Copyright | (C) 2015-2016 Edward Kmett Ryan Scott |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Ryan Scott |
Stability | Provisional |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Data.Functor.Classes.Generic.Internal
Description
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 {
- ghc8ShowBehavior :: Bool
- 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 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 where
- gliftCompare :: Ord1Args v a b -> t a -> t b -> Ordering
- 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 (forall a. Read a => GRead (f a)) => GRead1 v f where
- gliftReadPrec :: Read1Args v a -> ReadPrec (f a)
- class (forall a. Read a => GReadCon (f a)) => GRead1Con v f where
- gliftReadPrecCon :: ConType -> Read1Args v a -> ReadPrec (f a)
- 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 (forall a. Show a => GShow (f a)) => GShow1 v f where
- gliftShowsPrec :: Options -> Show1Args v a -> Int -> f a -> ShowS
- class (forall a. Show a => GShowCon (f a)) => GShow1Con v f where
- gliftShowsPrecCon :: Options -> ConType -> Show1Args v a -> Int -> f a -> ShowS
- data Show1Args v a where
- V4Show1Args :: Show a => Show1Args V4 a
- NonV4Show1Args :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a
- eqDefault :: (GEq (Rep1 f a), Generic1 f) => f a -> f a -> Bool
- class GEq a where
- geq :: a -> a -> Bool
- compareDefault :: (GOrd (Rep1 f a), Generic1 f) => f a -> f a -> Ordering
- class GEq a => GOrd a where
- gcompare :: a -> a -> Ordering
- readsPrecDefault :: (GRead (Rep1 f a), Generic1 f) => Int -> ReadS (f a)
- class GRead a where
- greadPrec :: ReadPrec a
- 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 a = FunctorClassesDefault {
- getFunctorClassesDefault :: f a
- data V4
- data NonV4
- data ConType
- class IsNullaryDataType f where
- isNullaryDataType :: f a -> Bool
- class IsNullaryCon f where
- isNullaryCon :: f a -> Bool
Options
Options that further configure how the functions in Data.Functor.Classes.Generic should behave.
Constructors
Options | |
Fields
|
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 #
A sensible default liftEq
implementation for Generic1
instances.
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 where Source #
Class of generic representation types that can lift equality through unary type constructors.
Instances
data Eq1Args v a b where Source #
An Eq1Args
value either stores an Eq a
dictionary (for the
transformers-0.4
version of Eq1
), or it stores the function argument that
checks the equality of occurrences of the type parameter (for the
non-transformers-0.4
version of Eq1
).
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 where Source #
Class of generic representation types that can lift a total order through unary type constructors.
Methods
gliftCompare :: Ord1Args v a b -> t a -> t b -> Ordering Source #
Instances
GOrd1 NonV4 Par1 Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args NonV4 a b -> Par1 a -> Par1 b -> Ordering Source # | |
GOrd1 v (U1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> U1 a -> U1 b -> Ordering Source # | |
GOrd1 v (UAddr :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> UAddr a -> UAddr b -> Ordering Source # | |
GOrd1 v (UChar :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> UChar a -> UChar b -> Ordering Source # | |
GOrd1 v (UDouble :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> UDouble a -> UDouble b -> Ordering Source # | |
GOrd1 v (UFloat :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> UFloat a -> UFloat b -> Ordering Source # | |
GOrd1 v (UInt :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> UInt a -> UInt b -> Ordering Source # | |
GOrd1 v (UWord :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> UWord a -> UWord b -> Ordering Source # | |
GOrd1 v (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> V1 a -> V1 b -> Ordering Source # | |
Ord1 f => GOrd1 NonV4 (Rec1 f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args NonV4 a b -> Rec1 f a -> Rec1 f b -> Ordering Source # | |
(GOrd1 v f, GOrd1 v g) => GOrd1 v (f :*: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> (f :*: g) a -> (f :*: g) b -> Ordering Source # | |
(GOrd1 v f, GOrd1 v g) => GOrd1 v (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> (f :+: g) a -> (f :+: g) b -> Ordering Source # | |
Ord c => GOrd1 v (K1 i c :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> K1 i c a -> K1 i c b -> Ordering Source # | |
(Ord1 f, GOrd1 NonV4 g) => GOrd1 NonV4 (f :.: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args NonV4 a b -> (f :.: g) a -> (f :.: g) b -> Ordering Source # | |
GOrd1 v f => GOrd1 v (M1 i c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftCompare :: Ord1Args v a b -> M1 i c f a -> M1 i c f b -> Ordering 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
).
Constructors
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 (forall a. Read a => GRead (f a)) => GRead1 v f where Source #
Class of generic representation types for unary type constructors that can
be parsed from a Lexeme
.
Methods
gliftReadPrec :: Read1Args v a -> ReadPrec (f a) Source #
Instances
GRead1 v (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftReadPrec :: Read1Args v a -> ReadPrec (V1 a) Source # | |
(GRead1 v f, GRead1 v g) => GRead1 v (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftReadPrec :: Read1Args v a -> ReadPrec ((f :+: g) a) Source # | |
(Constructor c, GRead1Con v f, IsNullaryCon f) => GRead1 v (C1 c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftReadPrec :: Read1Args v a -> ReadPrec (C1 c f a) Source # | |
(GRead1 v f, IsNullaryDataType f) => GRead1 v (D1 d f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftReadPrec :: Read1Args v a -> ReadPrec (D1 d f a) Source # |
class (forall a. Read a => GReadCon (f a)) => GRead1Con v f where Source #
Class of generic representation types for unary type constructors that
can be parsed from a Lexeme
, and for which the ConType
has been
determined.
Methods
gliftReadPrecCon :: ConType -> Read1Args v a -> ReadPrec (f a) Source #
Instances
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
).
Constructors
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 (forall a. Show a => GShow (f a)) => GShow1 v f where Source #
Class of generic representation types for unary type constructors that can
be converted to a Lexeme
.
Methods
gliftShowsPrec :: Options -> Show1Args v a -> Int -> f a -> ShowS Source #
Instances
GShow1 v (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftShowsPrec :: Options -> Show1Args v a -> Int -> V1 a -> ShowS Source # | |
(GShow1 v f, GShow1 v g) => GShow1 v (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftShowsPrec :: Options -> Show1Args v a -> Int -> (f :+: g) a -> ShowS Source # | |
(Constructor c, GShow1Con v f, IsNullaryCon f) => GShow1 v (C1 c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftShowsPrec :: Options -> Show1Args v a -> Int -> C1 c f a -> ShowS Source # | |
GShow1 v f => GShow1 v (D1 d f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gliftShowsPrec :: Options -> Show1Args v a -> Int -> D1 d f a -> ShowS Source # |
class (forall a. Show a => GShowCon (f a)) => GShow1Con v f where Source #
Class of generic representation types for unary type constructors that can
be converted to a Lexeme
, 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
).
Constructors
V4Show1Args :: Show a => Show1Args V4 a | |
NonV4Show1Args :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a |
Eq
eqDefault :: (GEq (Rep1 f a), Generic1 f) => f a -> f a -> Bool Source #
A default (
implementation for ==
)Generic1
instances that leverages
Eq1
.
Class of generic representation types that can be checked for equality.
Instances
Ord
compareDefault :: (GOrd (Rep1 f a), Generic1 f) => f a -> f a -> Ordering Source #
A default compare
implementation for Generic1
instances that leverages
Ord1
.
class GEq a => GOrd a where Source #
Class of generic representation types that can be totally ordered.
Instances
Read
readsPrecDefault :: (GRead (Rep1 f a), Generic1 f) => Int -> ReadS (f a) Source #
A default readsPrec
implementation for Generic1
instances that leverages
Read1
.
Class of generic representation types that can be parsed from a Lexeme
.
Instances
GRead (V1 p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GRead (f p), GRead (g p)) => GRead ((f :+: g) p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(Constructor c, GReadCon (f p), IsNullaryCon f) => GRead (C1 c f p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal | |
(GRead (f p), IsNullaryDataType f) => GRead (D1 d f p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal |
Show
showsPrecDefault :: (GShow (Rep1 f a), Generic1 f) => Int -> f a -> ShowS Source #
A default showsPrec
implementation for Generic1
instances that leverages
Show1
.
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 Lexeme
.
Methods
gshowsPrec :: Options -> Int -> a -> ShowS Source #
Instances
GShow (V1 p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gshowsPrec :: Options -> Int -> V1 p -> ShowS Source # | |
(GShow (f p), GShow (g p)) => GShow ((f :+: g) p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gshowsPrec :: Options -> Int -> (f :+: g) p -> ShowS Source # | |
(Constructor c, GShowCon (f p), IsNullaryCon f) => GShow (C1 c f p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gshowsPrec :: Options -> Int -> C1 c f p -> ShowS Source # | |
GShow (f p) => GShow (D1 d f p) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods gshowsPrec :: Options -> Int -> D1 d f p -> ShowS Source # |
FunctorClassesDefault
newtype FunctorClassesDefault f a Source #
An adapter newtype, suitable for DerivingVia
. Its Eq1
, Ord1
,
Read1
, and Show1
instances leverage Generic1
-based defaults.
Constructors
FunctorClassesDefault | |
Fields
|
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
class IsNullaryDataType f where Source #
Class of generic representation types that represent a data type with zero or more constructors.
Instances
IsNullaryDataType (V1 :: Type -> Type) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods isNullaryDataType :: V1 a -> Bool Source # | |
IsNullaryDataType (f :+: g) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods isNullaryDataType :: (f :+: g) a -> Bool Source # | |
IsNullaryDataType (C1 c f) Source # | |
Defined in Data.Functor.Classes.Generic.Internal Methods isNullaryDataType :: C1 c f a -> Bool Source # |
class IsNullaryCon f where Source #
Class of generic representation types that represent a constructor with zero or more fields.