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 | Haskell2010 |
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.
Synopsis
- 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 (forall a. Eq a => GEq (t a)) => GEq1 v (t :: Type -> Type) 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, forall a. Ord a => GOrd (t a)) => GOrd1 v (t :: Type -> Type) where
- gliftCompare :: Ord1Args v a b -> t a -> t b -> Ordering
- data Ord1Args v a b where
- V4Ord1Args :: forall a. Ord a => Ord1Args V4 a a
- NonV4Ord1Args :: forall a b. (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 (forall a. Read a => GRead (f a)) => GRead1 v (f :: Type -> Type) where
- gliftReadPrec :: Read1Args v a -> ReadPrec (f a)
- class (forall a. Read a => GReadCon (f a)) => GRead1Con v (f :: Type -> Type) where
- gliftReadPrecCon :: ConType -> Read1Args v a -> ReadPrec (f a)
- data Read1Args v a where
- V4Read1Args :: forall a. Read a => Read1Args V4 a
- NonV4Read1Args :: forall a. 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 (forall a. Show a => GShow (f a)) => GShow1 v (f :: Type -> Type) where
- gliftShowsPrec :: Options -> Show1Args v a -> Int -> f a -> ShowS
- class (forall a. Show a => GShowCon (f a)) => GShow1Con v (f :: Type -> Type) where
- data Show1Args v a where
- V4Show1Args :: forall a. Show a => Show1Args V4 a
- NonV4Show1Args :: forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a
- eqDefault :: (GEq (Rep1 f a), Generic1 f) => f a -> f a -> Bool
- class GEq a where
- compareDefault :: (GOrd (Rep1 f a), Generic1 f) => f a -> f a -> Ordering
- class GEq a => GOrd a where
- readsPrecDefault :: (GRead (Rep1 f a), Generic1 f) => Int -> ReadS (f a)
- class GRead a where
- showsPrecDefault :: (GShow (Rep1 f a), Generic1 f) => Int -> f a -> ShowS
- showsPrecOptions :: (GShow (Rep1 f a), Generic1 f) => Options -> Int -> f a -> ShowS
- class GShow a where
- gshowsPrec :: Options -> Int -> a -> ShowS
- newtype FunctorClassesDefault (f :: Type -> Type) a = FunctorClassesDefault {
- getFunctorClassesDefault :: f a
- data V4
- data NonV4
- data ConType
- class IsNullaryDataType (f :: Type -> Type) where
- isNullaryDataType :: f a -> Bool
- class IsNullaryCon (f :: Type -> Type) where
- isNullaryCon :: f a -> Bool
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 (forall a. Eq a => GEq (t a)) => GEq1 v (t :: Type -> Type) where Source #
Class of generic representation types that can lift equality through unary type constructors.
Instances
GEq1 NonV4 Par1 Source # | |
GEq1 v (U1 :: Type -> Type) Source # | |
GEq1 v (UAddr :: Type -> Type) Source # | |
GEq1 v (UChar :: Type -> Type) Source # | |
GEq1 v (UDouble :: Type -> Type) Source # | |
GEq1 v (UFloat :: Type -> Type) Source # | |
GEq1 v (UInt :: Type -> Type) Source # | |
GEq1 v (UWord :: Type -> Type) Source # | |
GEq1 v (V1 :: Type -> Type) 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 :: Type -> Type) Source # | |
(Eq1 f, GEq1 NonV4 g) => GEq1 NonV4 (f :.: g) Source # | |
GEq1 v f => GEq1 v (M1 i c f) 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, forall a. Ord a => GOrd (t a)) => GOrd1 v (t :: Type -> Type) where Source #
Class of generic representation types that can lift a total order through unary type constructors.
gliftCompare :: Ord1Args v a b -> t a -> t b -> Ordering Source #
Instances
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 :: forall a. Ord a => Ord1Args V4 a a | |
NonV4Ord1Args :: forall a b. (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 (forall a. Read a => GRead (f a)) => GRead1 v (f :: Type -> Type) where Source #
Class of generic representation types for unary type constructors that can
be parsed from a String
.
gliftReadPrec :: Read1Args v a -> ReadPrec (f a) Source #
Instances
GRead1 v (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GRead1 v f, GRead1 v g) => GRead1 v (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Constructor c, GRead1Con v f, IsNullaryCon f) => GRead1 v (C1 c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GRead1 v f, IsNullaryDataType f) => GRead1 v (D1 d f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal |
class (forall a. Read a => GReadCon (f a)) => GRead1Con v (f :: Type -> Type) where Source #
Class of generic representation types for unary type constructors that
can be parsed from a String
, and for which the ConType
has been
determined.
Instances
GRead1Con NonV4 Par1 Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
GRead1Con v (U1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
Read1 f => GRead1Con NonV4 (Rec1 f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GRead1Con v f, GRead1Con v g) => GRead1Con v (f :*: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
Read c => GRead1Con v (K1 i c :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Selector s, GRead1Con v f) => GRead1Con v (S1 s f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Read1 f, GRead1Con NonV4 g) => GRead1Con NonV4 (f :.: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal |
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 :: forall a. Read a => Read1Args V4 a | |
NonV4Read1Args :: forall a. 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 (forall a. Show a => GShow (f a)) => GShow1 v (f :: Type -> Type) where Source #
Class of generic representation types for unary type constructors that can
be converted to a String
.
Instances
GShow1 v (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GShow1 v f, GShow1 v g) => GShow1 v (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Constructor c, GShow1Con v f, IsNullaryCon f) => GShow1 v (C1 c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
GShow1 v f => GShow1 v (D1 d f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal |
class (forall a. Show a => GShowCon (f a)) => GShow1Con v (f :: Type -> Type) where Source #
Class of generic representation types for unary type constructors that can
be converted to a String
, and for which the ConType
has been determined.
Instances
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 :: forall a. Show a => Show1Args V4 a | |
NonV4Show1Args :: forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a |
Eq
Class of generic representation types that can be checked for equality.
Instances
Eq p => GEq (Par1 p) Source # | |
GEq (U1 p) Source # | |
GEq (UAddr p) Source # | |
GEq (UChar p) Source # | |
GEq (UDouble p) Source # | |
GEq (UFloat p) Source # | |
GEq (UInt p) Source # | |
GEq (UWord p) Source # | |
GEq (V1 p) Source # | |
(Eq1 f, Eq p) => GEq (Rec1 f p) Source # | |
(GEq (f p), GEq (g p)) => GEq ((f :*: g) p) Source # | |
(GEq (f p), GEq (g p)) => GEq ((f :+: g) p) Source # | |
Eq c => GEq (K1 i c p) Source # | |
(Eq1 f, GEq (g p)) => GEq ((f :.: g) p) Source # | |
GEq (f p) => GEq (M1 i c f p) Source # | |
Ord
class GEq a => GOrd a where Source #
Class of generic representation types that can be totally ordered.
Instances
Ord p => GOrd (Par1 p) Source # | |
GOrd (U1 p) Source # | |
GOrd (UAddr p) Source # | |
GOrd (UChar p) Source # | |
GOrd (UDouble p) Source # | |
GOrd (UFloat p) Source # | |
GOrd (UInt p) Source # | |
GOrd (UWord p) Source # | |
GOrd (V1 p) Source # | |
(Ord1 f, Ord p) => GOrd (Rec1 f p) Source # | |
(GOrd (f p), GOrd (g p)) => GOrd ((f :*: g) p) Source # | |
(GOrd (f p), GOrd (g p)) => GOrd ((f :+: g) p) Source # | |
Ord c => GOrd (K1 i c p) Source # | |
(Ord1 f, GOrd (g p)) => GOrd ((f :.: g) p) Source # | |
GOrd (f p) => GOrd (M1 i c f p) Source # | |
Read
Class of generic representation types that can be parsed from a String
.
Show
showsPrecOptions :: (GShow (Rep1 f a), Generic1 f) => Options -> Int -> f a -> ShowS Source #
Like showsPrecDefault
, but with configurable Options
.
Class of generic representation types that can be converted to a String
.
Instances
GShow (V1 p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GShow (f p), GShow (g p)) => GShow ((f :+: g) p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Constructor c, GShowCon (f p), IsNullaryCon f) => GShow (C1 c f p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
GShow (f p) => GShow (D1 d f p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal |
FunctorClassesDefault
newtype FunctorClassesDefault (f :: Type -> Type) a Source #
An adapter newtype, suitable for DerivingVia
. Its Eq1
, Ord1
,
Read1
, and Show1
instances leverage Generic1
-based defaults.
Instances
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.
Instances
GEq1 NonV4 Par1 Source # | |
GOrd1 NonV4 Par1 Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
GRead1Con NonV4 Par1 Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
GShow1Con NonV4 Par1 Source # | |
Eq1 f => GEq1 NonV4 (Rec1 f) Source # | |
Ord1 f => GOrd1 NonV4 (Rec1 f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
Read1 f => GRead1Con NonV4 (Rec1 f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
Show1 f => GShow1Con NonV4 (Rec1 f) Source # | |
(Eq1 f, GEq1 NonV4 g) => GEq1 NonV4 (f :.: g) Source # | |
(Ord1 f, GOrd1 NonV4 g) => GOrd1 NonV4 (f :.: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Read1 f, GRead1Con NonV4 g) => GRead1Con NonV4 (f :.: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Show1 f, GShow1Con NonV4 g) => GShow1Con NonV4 (f :.: g) Source # | |
class IsNullaryDataType (f :: Type -> Type) where Source #
Class of generic representation types that represent a data type with zero or more constructors.
isNullaryDataType :: f a -> Bool Source #
Returns True
if the data type has no constructors.
Instances
IsNullaryDataType (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal isNullaryDataType :: V1 a -> Bool Source # | |
IsNullaryDataType (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal isNullaryDataType :: (f :+: g) a -> Bool Source # | |
IsNullaryDataType (C1 c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal isNullaryDataType :: C1 c f a -> Bool Source # |
class IsNullaryCon (f :: Type -> Type) where Source #
Class of generic representation types that represent a constructor with zero or more fields.
isNullaryCon :: f a -> Bool Source #
Returns True
if the constructor has no fields.