Copyright | (C) 2015-2016 Edward Kmett Ryan Scott |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Ryan Scott |
Stability | Provisional |
Portability | GHC |
Safe Haskell | None |
Language | Haskell98 |
Internal functionality for Data.Functor.Classes.Generic.
This is an internal module and, as such, the API is not guaranteed to remain the same between any given release.
- newtype Options = Options {}
- defaultOptions :: Options
- latestGHCOptions :: Options
- liftEqDefault :: (GEq1 NonV4 (Rep1 f), Generic1 f) => (a -> b -> Bool) -> f a -> f b -> Bool
- liftEqOptions :: (GEq1 NonV4 (Rep1 f), Generic1 f) => Options -> (a -> b -> Bool) -> f a -> f b -> Bool
- class GEq1 v t where
- data Eq1Args v a b where
- liftCompareDefault :: (GOrd1 NonV4 (Rep1 f), Generic1 f) => (a -> b -> Ordering) -> f a -> f b -> Ordering
- liftCompareOptions :: (GOrd1 NonV4 (Rep1 f), Generic1 f) => Options -> (a -> b -> Ordering) -> f a -> f b -> Ordering
- class GEq1 v t => GOrd1 v t where
- data Ord1Args v a b where
- V4Ord1Args :: Ord a => Ord1Args V4 a a
- NonV4Ord1Args :: (a -> b -> Ordering) -> Ord1Args NonV4 a b
- liftReadsPrecDefault :: (GRead1 NonV4 (Rep1 f), Generic1 f) => (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
- liftReadsPrecOptions :: (GRead1 NonV4 (Rep1 f), Generic1 f) => Options -> (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
- class GRead1 v f where
- class GRead1Con v f where
- data Read1Args v a where
- V4Read1Args :: Read a => Read1Args V4 a
- NonV4Read1Args :: ReadPrec a -> ReadPrec [a] -> Read1Args NonV4 a
- liftShowsPrecDefault :: (GShow1 NonV4 (Rep1 f), Generic1 f) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
- liftShowsPrecOptions :: (GShow1 NonV4 (Rep1 f), Generic1 f) => Options -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
- class GShow1 v f where
- class GShow1Con v f where
- data Show1Args v a where
- V4Show1Args :: Show a => Show1Args V4 a
- NonV4Show1Args :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a
- data V4
- data NonV4
- data ConType
- class IsNullary f where
Options
Options that further configure how the functions in Data.Functor.Classes.Generic should behave.
defaultOptions :: Options Source #
Options that match the behavior of the installed version of GHC.
latestGHCOptions :: Options Source #
Options that match the behavior of the most recent GHC release.
Eq1
liftEqDefault :: (GEq1 NonV4 (Rep1 f), Generic1 f) => (a -> b -> Bool) -> f a -> f b -> Bool Source #
liftEqOptions :: (GEq1 NonV4 (Rep1 f), Generic1 f) => Options -> (a -> b -> Bool) -> f a -> f b -> Bool Source #
Like liftEqDefault
, but with configurable Options
. Currently,
the Options
have no effect (but this may change in the future).
Class of generic representation types that can be checked for equality.
GEq1 NonV4 Par1 Source # | |
GEq1 v (UWord *) Source # | |
GEq1 v (UInt *) Source # | |
GEq1 v (UFloat *) Source # | |
GEq1 v (UDouble *) Source # | |
GEq1 v (UChar *) Source # | |
GEq1 v (UAddr *) Source # | |
GEq1 v (V1 *) Source # | |
GEq1 v (U1 *) Source # | |
Eq1 f => GEq1 NonV4 (Rec1 * f) Source # | |
(GEq1 v f, GEq1 v g) => GEq1 v ((:+:) * f g) Source # | |
(GEq1 v f, GEq1 v g) => GEq1 v ((:*:) * f g) Source # | |
Eq c => GEq1 v (K1 * i c) Source # | |
GEq1 v f => GEq1 v (M1 * i c f) Source # | |
(Eq1 f, GEq1 NonV4 g) => GEq1 NonV4 ((:.:) * * f g) Source # | |
Ord1
liftCompareDefault :: (GOrd1 NonV4 (Rep1 f), Generic1 f) => (a -> b -> Ordering) -> f a -> f b -> Ordering Source #
A sensible default liftCompare
implementation for Generic1
instances.
liftCompareOptions :: (GOrd1 NonV4 (Rep1 f), Generic1 f) => Options -> (a -> b -> Ordering) -> f a -> f b -> Ordering Source #
Like liftCompareDefault
, but with configurable Options
. Currently,
the Options
have no effect (but this may change in the future).
class GEq1 v t => GOrd1 v t where Source #
Class of generic representation types that can be totally ordered.
gliftCompare :: Ord1Args v a b -> t a -> t b -> Ordering Source #
GOrd1 NonV4 Par1 Source # | |
GOrd1 v (UWord *) Source # | |
GOrd1 v (UInt *) Source # | |
GOrd1 v (UFloat *) Source # | |
GOrd1 v (UDouble *) Source # | |
GOrd1 v (UChar *) Source # | |
GOrd1 v (UAddr *) Source # | |
GOrd1 v (V1 *) Source # | |
GOrd1 v (U1 *) Source # | |
Ord1 f => GOrd1 NonV4 (Rec1 * f) Source # | |
(GOrd1 v f, GOrd1 v g) => GOrd1 v ((:+:) * f g) Source # | |
(GOrd1 v f, GOrd1 v g) => GOrd1 v ((:*:) * f g) Source # | |
Ord c => GOrd1 v (K1 * i c) Source # | |
GOrd1 v f => GOrd1 v (M1 * i c f) Source # | |
(Ord1 f, GOrd1 NonV4 g) => GOrd1 NonV4 ((:.:) * * f g) Source # | |
data Ord1Args v a b where Source #
An Ord1Args
value either stores an Ord a
dictionary (for the
transformers-0.4
version of Ord1
), or it stores the function argument that
compares occurrences of the type parameter (for the non-transformers-0.4
version of Ord1
).
V4Ord1Args :: Ord a => Ord1Args V4 a a | |
NonV4Ord1Args :: (a -> b -> Ordering) -> Ord1Args NonV4 a b |
Read1
liftReadsPrecDefault :: (GRead1 NonV4 (Rep1 f), Generic1 f) => (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) Source #
A sensible default liftReadsPrec
implementation for Generic1
instances.
liftReadsPrecOptions :: (GRead1 NonV4 (Rep1 f), Generic1 f) => Options -> (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) Source #
Like liftReadsPrecDefault
, but with configurable Options
. Currently,
the Options
have no effect (but this may change in the future).
class GRead1 v f where Source #
Class of generic representation types that can be parsed from a String
.
gliftReadPrec :: Read1Args v a -> ReadPrec (f a) Source #
class GRead1Con v f where Source #
Class of generic representation types that can be parsed from a String
, and
for which the ConType
has been determined.
GRead1Con NonV4 Par1 Source # | |
GRead1Con v (U1 *) Source # | |
Read1 f => GRead1Con NonV4 (Rec1 * f) Source # | |
(GRead1Con v f, GRead1Con v g) => GRead1Con v ((:*:) * f g) Source # | |
(Selector Meta s, GRead1Con v f) => GRead1Con v (S1 * s f) Source # | |
Read c => GRead1Con v (K1 * i c) Source # | |
(Read1 f, GRead1Con NonV4 g) => GRead1Con NonV4 ((:.:) * * f g) Source # | |
data Read1Args v a where Source #
A Read1Args
value either stores a Read a
dictionary (for the
transformers-0.4
version of Read1
), or it stores the two function arguments
that parse occurrences of the type parameter (for the non-transformers-0.4
version of Read1
).
V4Read1Args :: Read a => Read1Args V4 a | |
NonV4Read1Args :: ReadPrec a -> ReadPrec [a] -> Read1Args NonV4 a |
Show1
liftShowsPrecDefault :: (GShow1 NonV4 (Rep1 f), Generic1 f) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #
A sensible default liftShowsPrec
implementation for Generic1
instances.
liftShowsPrecOptions :: (GShow1 NonV4 (Rep1 f), Generic1 f) => Options -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #
Like liftShowsPrecDefault
, but with configurable Options
.
class GShow1 v f where Source #
Class of generic representation types that can be converted to a String
.
class GShow1Con v f where Source #
Class of generic representation types that can be converted to a String
, and
for which the ConType
has been determined.
GShow1Con NonV4 Par1 Source # | |
GShow1Con v (UWord *) Source # | |
GShow1Con v (UInt *) Source # | |
GShow1Con v (UFloat *) Source # | |
GShow1Con v (UDouble *) Source # | |
GShow1Con v (UChar *) Source # | |
GShow1Con v (U1 *) Source # | |
Show1 f => GShow1Con NonV4 (Rec1 * f) Source # | |
(GShow1Con v f, GShow1Con v g) => GShow1Con v ((:*:) * f g) Source # | |
(Selector Meta s, GShow1Con v f) => GShow1Con v (S1 * s f) Source # | |
Show c => GShow1Con v (K1 * i c) Source # | |
(Show1 f, GShow1Con NonV4 g) => GShow1Con NonV4 ((:.:) * * f g) Source # | |
data Show1Args v a where Source #
A Show1Args
value either stores a Show a
dictionary (for the
transformers-0.4
version of Show1
), or it stores the two function arguments
that show occurrences of the type parameter (for the non-transformers-0.4
version of Show1
).
V4Show1Args :: Show a => Show1Args V4 a | |
NonV4Show1Args :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a |
Miscellaneous types
A type-level indicator that the transformers-0.4
version of a class method
is being derived generically.
A type-level indicator that the non-transformers-0.4
version of a class
method is being derived generically.
GShow1Con NonV4 Par1 Source # | |
GRead1Con NonV4 Par1 Source # | |
GOrd1 NonV4 Par1 Source # | |
GEq1 NonV4 Par1 Source # | |
Show1 f => GShow1Con NonV4 (Rec1 * f) Source # | |
Read1 f => GRead1Con NonV4 (Rec1 * f) Source # | |
Ord1 f => GOrd1 NonV4 (Rec1 * f) Source # | |
Eq1 f => GEq1 NonV4 (Rec1 * f) Source # | |
(Show1 f, GShow1Con NonV4 g) => GShow1Con NonV4 ((:.:) * * f g) Source # | |
(Read1 f, GRead1Con NonV4 g) => GRead1Con NonV4 ((:.:) * * f g) Source # | |
(Ord1 f, GOrd1 NonV4 g) => GOrd1 NonV4 ((:.:) * * f g) Source # | |
(Eq1 f, GEq1 NonV4 g) => GEq1 NonV4 ((:.:) * * f g) Source # | |
class IsNullary f where Source #
Class of generic representation types that represent a constructor with zero or more fields.
IsNullary Par1 Source # | |
IsNullary (U1 *) Source # | |
IsNullary (UChar *) Source # | |
IsNullary (UDouble *) Source # | |
IsNullary (UFloat *) Source # | |
IsNullary (UInt *) Source # | |
IsNullary (UWord *) Source # | |
IsNullary (Rec1 * f) Source # | |
IsNullary (K1 * i c) Source # | |
IsNullary ((:*:) * f g) Source # | |
IsNullary f => IsNullary (S1 * s f) Source # | |
IsNullary ((:.:) * * f g) Source # | |