| Copyright | (c) Universiteit Utrecht 2010-2011 University of Oxford 2012-2014 |
|---|---|
| License | see libraries/base/LICENSE |
| Maintainer | libraries@haskell.org |
| Stability | internal |
| Portability | non-portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
GHC.Generics
Contents
Description
If you're usingGHC.Generics, you should consider using thehttp://hackage.haskell.org/package/generic-deriving package, which contains many useful generic functions.
Since: 4.6.0.0
Datatype-generic functions are based on the idea of converting values of a datatypeT into corresponding values of a (nearly) isomorphic type. The typeRep T is built from a limited set of type constructors, all provided by this module. A datatype-generic function is then an overloaded function with instances for most of these type constructors, together with a wrapper that performs the mapping betweenRep TT and. By using this technique, we merely need a few generic instances in order to implement functionality that works for any representable type.Rep T
Representable types are collected in theGeneric class, which defines the associated typeRep as well as conversion functionsfrom andto. Typically, you will not defineGeneric instances by hand, but have the compiler derive them for you.
The key to defining your own datatype-generic functions is to understand how to represent datatypes using the given set of type constructors.
Let us look at an example first:
data Tree a = Leaf a | Node (Tree a) (Tree a) derivingGenericThe above declaration (which requires the language pragmaDeriveGeneric) causes the following representation to be generated:
instanceGeneric(Tree a) where typeRep(Tree a) =D1('MetaData "Tree" "Main" "package-name" 'False) (C1('MetaCons "Leaf" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0a)):+:C1('MetaCons "Node" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0(Tree a)):*:S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0(Tree a)))) ...
Hint: You can obtain information about the code being generated from GHC by passing the-ddump-deriv flag. In GHCi, you can expand a type family such asRep using the:kind! command.
This is a lot of information! However, most of it is actually merely meta-information that makes names of datatypes and constructors and more available on the type level.
Here is a reduced representation forTree with nearly all meta-information removed, for now keeping only the most essential aspects:
instanceGeneric(Tree a) where typeRep(Tree a) =Rec0a:+:(Rec0(Tree a):*:Rec0(Tree a))
TheTree datatype has two constructors. The representation of individual constructors is combined using the binary type constructor:+:.
The first constructor consists of a single field, which is the parametera. This is represented as.Rec0 a
The second constructor consists of two fields. Each is a recursive field of typeTree a, represented as. Representations of individual fields are combined using the binary type constructorRec0 (Tree a):*:.
Now let us explain the additional tags being used in the complete representation:
S1 ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) tag indicates several things. The'Nothing indicates that there is no record field selector associated with this field of the constructor (if there were, it would have been marked'Just "recordName" instead). The other types contain meta-information on the field's strictness:{-# UNPACK #-} or{-# NOUNPACK #-} annotation in the source, so it is tagged with'NoSourceUnpackedness.!) or laziness (~) annotation in the source, so it is tagged with'NoSourceStrictness.'DecidedLazy. Bear in mind that what the compiler decides may be quite different from what is written in the source. SeeDecidedStrictness for a more detailed explanation.The'MetaSel type is also an instance of the type classSelector, which can be used to obtain information about the field at the value level.
C1 ('MetaCons "Leaf" 'PrefixI 'False) andC1 ('MetaCons "Node" 'PrefixI 'False) invocations indicate that the enclosed part is the representation of the first and second constructor of datatypeTree, respectively. Here, the meta-information regarding constructor names, fixity and whether it has named fields or not is encoded at the type level. The'MetaCons type is also an instance of the type classConstructor. This type class can be used to obtain information about the constructor at the value level.D1 ('MetaData "Tree" "Main" "package-name" 'False) tag indicates that the enclosed part is the representation of the datatypeTree. Again, the meta-information is encoded at the type level. The'MetaData type is an instance of classDatatype, which can be used to obtain the name of a datatype, the module it has been defined in, the package it is located under, and whether it has been defined usingdata ornewtype at the value level.There are many datatype-generic functions that do not distinguish between positions that are parameters or positions that are recursive calls. There are also many datatype-generic functions that do not care about the names of datatypes and constructors at all. To keep the number of cases to consider in generic functions in such a situation to a minimum, it turns out that many of the type constructors introduced above are actually synonyms, defining them to be variants of a smaller set of constructors.
K1The type constructorRec0 is a variant ofK1:
typeRec0=K1R
Here,R is a type-level proxy that does not have any associated values.
There used to be another variant ofK1 (namelyPar0), but it has since been deprecated.
M1The type constructorsS1,C1 andD1 are all variants ofM1:
typeS1=M1StypeC1=M1CtypeD1=M1D
The typesS,C andD are once again type-level proxies, just used to create several variants ofM1.
Next toK1,M1,:+: and:*: there are a few more type constructors that occur in the representations of other datatypes.
V1For empty datatypes,V1 is used as a representation. For example,
data Empty derivingGenericyields
instanceGenericEmpty where typeRepEmpty =D1('MetaData "Empty" "Main" "package-name" 'False)V1
U1If a constructor has no arguments, thenU1 is used as its representation. For example the representation ofBool is
instanceGenericBool where typeRepBool =D1('MetaData "Bool" "Data.Bool" "package-name" 'False) (C1('MetaCons "False" 'PrefixI 'False)U1:+:C1('MetaCons "True" 'PrefixI 'False)U1)
As:+: and:*: are just binary operators, one might ask what happens if the datatype has more than two constructors, or a constructor with more than two fields. The answer is simple: the operators are used several times, to combine all the constructors and fields as needed. However, users /should not rely on a specific nesting strategy/ for:+: and:*: being used. The compiler is free to choose any nesting it prefers. (In practice, the current implementation tries to produce a more-or-less balanced nesting, so that the traversal of the structure of the datatype from the root to a particular component can be performed in logarithmic rather than linear time.)
A datatype-generic function comprises two parts:
Generic, performs the conversion between the original value and itsRep-based representation and then invokes the generic instances.As an example, let us look at a functionencode that produces a naive, but lossless bit encoding of values of various datatypes. So we are aiming to define a function
encode ::Generic a => a -> [Bool]where we useBool as our datatype for bits.
For part 1, we define a classEncode'. Perhaps surprisingly, this class is parameterized over a type constructorf of kind* -> *. This is a technicality: all the representation type constructors operate with kind* -> * as base kind. But the type argument is never being used. This may be changed at some point in the future. The class has a single method, and we use the type we want our final function to have, but we replace the occurrences of the generic type argumenta withf p (where thep is any argument; it will not be used).
class Encode' f where encode' :: f p -> [Bool]
With the goal in mind to makeencode work onTree and other datatypes, we now define instances for the representation type constructorsV1,U1,:+:,:*:,K1, andM1.
In order to be able to do this, we need to know the actual definitions of these types:
dataV1p -- lifted version of EmptydataU1p =U1-- lifted version of ()data (:+:) f g p =L1(f p) |R1(g p) -- lifted version ofEitherdata (:*:) f g p = (f p):*:(g p) -- lifted version of (,)newtypeK1i c p =K1{unK1:: c } -- a container for a cnewtypeM1i t f p =M1{unM1:: f p } -- a wrapper
So,U1 is just the unit type,:+: is just a binary choice likeEither,:*: is a binary pair like the pair constructor(,), andK1 is a value of a specific typec, andM1 wraps a value of the generic type argument, which in the lifted world is anf p (where we do not care aboutp).
The instance forV1 is slightly awkward (but also rarely used):
instance Encode'V1 where encode' x = undefinedThere are no values of typeV1 p to pass (except undefined), so this is actually impossible. One can ask why it is useful to define an instance forV1 at all in this case? Well, an empty type can be used as an argument to a non-empty type, and you might still want to encode the resulting type. As a somewhat contrived example, consider[Empty], which is not an empty type, but contains just the empty list. TheV1 instance ensures that we can call the generic function on such types.
There is exactly one value of typeU1, so encoding it requires no knowledge, and we can use zero bits:
instance Encode'U1where encode'U1= []
In the case for:+:, we produceFalse orTrue depending on whether the constructor of the value provided is located on the left or on the right:
instance (Encode' f, Encode' g) => Encode' (f:+:g) where encode' (L1x) = False : encode' x encode' (R1x) = True : encode' x
(Note that this encoding strategy may not be reliable across different versions of GHC. Recall that the compiler is free to choose any nesting of:+: it chooses, so if GHC chooses(a, then the encoding for:+: b):+: ca would be[False, False],b would be[False, True], andc would be[True]. However, if GHC choosesa, then the encoding for:+: (b:+: c)a would be[False],b would be[True, False], andc would be[True, True].)
In the case for:*:, we append the encodings of the two subcomponents:
instance (Encode' f, Encode' g) => Encode' (f:*:g) where encode' (x:*:y) = encode' x ++ encode' y
The case forK1 is rather interesting. Here, we call the final functionencode that we yet have to define, recursively. We will use another type classEncode for that function:
instance (Encode c) => Encode' (K1i c) where encode' (K1x) = encode x
Note howPar0 andRec0 both being mapped toK1 allows us to define a uniform instance here.
Similarly, we can define a uniform instance forM1, because we completely disregard all meta-information:
instance (Encode' f) => Encode' (M1i t f) where encode' (M1x) = encode' x
Unlike inK1, the instance forM1 refers toencode', notencode.
We now define classEncode for the actualencode function:
class Encode a where encode :: a -> [Bool] default encode :: (Generic a, Encode' (Rep a)) => a -> [Bool] encode x = encode' (from x)The incomingx is converted usingfrom, then we dispatch to the generic instances usingencode'. We use this as a default definition forencode. We need the 'default encode' signature because ordinary Haskell default methods must not introduce additional class constraints, but our generic default does.
Defining a particular instance is now as simple as saying
instance (Encode a) => Encode (Tree a)
It is not always required to provide instances for all the generic representation types, but omitting instances restricts the set of datatypes the functions will work for:
:+: instance is given, the function may still work for empty datatypes or datatypes that have a single constructor, but will fail on datatypes with more than one constructor.:*: instance is given, the function may still work for datatypes where each constructor has just zero or one field, in particular for enumeration types.K1 instance is given, the function may still work for enumeration types, where no constructor has any fields.V1 instance is given, the function may still work for any datatype that is not empty.U1 instance is given, the function may still work for any datatype where each constructor has at least one field.AnM1 instance is always required (but it can just ignore the meta-information, as is the case forencode above).
Datatype-generic functions as defined above work for a large class of datatypes, including parameterized datatypes. (We have usedTree as our example above, which is of kind* -> *.) However, theGeneric class ranges over types of kind*, and therefore, the resulting generic functions (such asencode) must be parameterized by a generic type argument of kind*.
What if we want to define generic classes that range over type constructors (such asFunctor,Traversable, orFoldable)?
Generic1 classLikeGeneric, there is a classGeneric1 that defines a representationRep1 and conversion functionsfrom1 andto1, only thatGeneric1 ranges over types of kind* -> *. (More generally, it can range over types of kindk -> *, for any kindk, if thePolyKinds extension is enabled. More on this later.) TheGeneric1 class is also derivable.
The representationRep1 is ever so slightly different fromRep. Let us look atTree as an example again:
data Tree a = Leaf a | Node (Tree a) (Tree a) derivingGeneric1The above declaration causes the following representation to be generated:
instanceGeneric1Tree where typeRep1Tree =D1('MetaData "Tree" "Main" "package-name" 'False) (C1('MetaCons "Leaf" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)Par1):+:C1('MetaCons "Node" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1Tree):*:S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1Tree))) ...
The representation reusesD1,C1,S1 (and therebyM1) as well as:+: and:*: fromRep. (This reusability is the reason that we carry around the dummy type argument for kind-*-types, but there are already enough different names involved without duplicating each of these.)
What's different is that we now usePar1 to refer to the parameter (and that parameter, which used to bea), is not mentioned explicitly by name anywhere; and we useRec1 to refer to a recursive use ofTree a.
* -> * typesUnlikeRec0, thePar1 andRec1 type constructors do not map toK1. They are defined directly, as follows:
newtypePar1p =Par1{unPar1:: p } -- gives access to parameter pnewtypeRec1f p =Rec1{unRec1:: f p } -- a wrapper
InPar1, the parameterp is used for the first time, whereasRec1 simply wraps an application off top.
Note thatK1 (in the guise ofRec0) can still occur in aRep1 representation, namely when the datatype has a field that does not mention the parameter.
The declaration
data WithInt a = WithInt Int a derivingGeneric1yields
instanceGeneric1WithInt where typeRep1WithInt =D1('MetaData "WithInt" "Main" "package-name" 'False) (C1('MetaCons "WithInt" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0Int):*:S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)Par1))
If the parametera appears underneath a composition of other type constructors, then the representation involves composition, too:
data Rose a = Fork a [Rose a]
yields
instanceGeneric1Rose where typeRep1Rose =D1('MetaData "Rose" "Main" "package-name" 'False) (C1('MetaCons "Fork" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)Par1:*:S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([]:.:Rec1Rose)))
where
newtype (:.:) f g p =Comp1{unComp1:: f (g p) }
k -> * typesTheGeneric1 class can be generalized to range over types of kindk -> *, for any kindk. To do so, derive aGeneric1 instance with thePolyKinds extension enabled. For example, the declaration
data Proxy (a :: k) = Proxy derivingGeneric1yields a slightly different instance depending on whetherPolyKinds is enabled. If compiled withoutPolyKinds, then, but if compiled withRep1 Proxy :: * -> *PolyKinds, then.Rep1 Proxy :: k -> *
If one were to attempt to derive a Generic instance for a datatype with an unlifted argument (for example,Int#), one might expect the occurrence of theInt# argument to be marked with. This won't work, though, sinceRec0Int#Int# is of an unlifted kind, andRec0 expects a type of kind*.
One solution would be to represent an occurrence ofInt# with 'Rec0 Int' instead. With this approach, however, the programmer has no way of knowing whether theInt is actually anInt# in disguise.
Instead of reusingRec0, a separate data familyURec is used to mark occurrences of common unlifted types:
data family URec a pdata instanceURec(Ptr()) p =UAddr{uAddr#::Addr#}data instanceURecCharp =UChar{uChar#::Char#}data instanceURecDoublep =UDouble{uDouble#::Double#}data instanceURecIntp =UFloat{uFloat#::Float#}data instanceURecFloatp =UInt{uInt#::Int#}data instanceURecWordp =UWord{uWord#::Word#}
Several type synonyms are provided for convenience:
typeUAddr=URec(Ptr())typeUChar=URecChartypeUDouble=URecDoubletypeUFloat=URecFloattypeUInt=URecInttypeUWord=URecWord
The declaration
data IntHash = IntHash Int# derivingGenericyields
instanceGenericIntHash where typeRepIntHash =D1('MetaData "IntHash" "Main" "package-name" 'False) (C1('MetaCons "IntHash" 'PrefixI 'False) (S1('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)UInt))
Currently, only the six unlifted types listed above are generated, but this may be extended to encompass more unlifted types in the future.
Void: used for datatypes without constructors
| Generic1 (V1 :: k ->Type)Source# | |
| Functor (V1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Foldable (V1 ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>V1 m -> mSource# foldMap ::Monoid m => (a -> m) ->V1 a -> mSource# foldr :: (a -> b -> b) -> b ->V1 a -> bSource# foldr' :: (a -> b -> b) -> b ->V1 a -> bSource# foldl :: (b -> a -> b) -> b ->V1 a -> bSource# foldl' :: (b -> a -> b) -> b ->V1 a -> bSource# foldr1 :: (a -> a -> a) ->V1 a -> aSource# foldl1 :: (a -> a -> a) ->V1 a -> aSource# elem ::Eq a => a ->V1 a ->BoolSource# maximum ::Ord a =>V1 a -> aSource# minimum ::Ord a =>V1 a -> aSource# | |
| Traversable (V1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Contravariant (V1 ::Type ->Type)Source# | |
| Eq (V1 p)Source# | Since: 4.9.0.0 |
| Data p =>Data (V1 p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->V1 p -> c (V1 p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (V1 p)Source# toConstr ::V1 p ->ConstrSource# dataTypeOf ::V1 p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (V1 p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (V1 p))Source# gmapT :: (forall b.Data b => b -> b) ->V1 p ->V1 pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->V1 p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->V1 p -> rSource# gmapQ :: (forall d.Data d => d -> u) ->V1 p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->V1 p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->V1 p -> m (V1 p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->V1 p -> m (V1 p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->V1 p -> m (V1 p)Source# | |
| Ord (V1 p)Source# | Since: 4.9.0.0 |
| Read (V1 p)Source# | Since: 4.9.0.0 |
| Show (V1 p)Source# | Since: 4.9.0.0 |
| Generic (V1 p)Source# | |
| Semigroup (V1 p)Source# | Since: 4.12.0.0 |
| typeRep1 (V1 :: k ->Type)Source# | Since: 4.9.0.0 |
| typeRep (V1 p)Source# | Since: 4.9.0.0 |
Unit: used for constructors without arguments
Constructors
| U1 |
| Generic1 (U1 :: k ->Type)Source# | |
| Monad (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Functor (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Applicative (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Foldable (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>U1 m -> mSource# foldMap ::Monoid m => (a -> m) ->U1 a -> mSource# foldr :: (a -> b -> b) -> b ->U1 a -> bSource# foldr' :: (a -> b -> b) -> b ->U1 a -> bSource# foldl :: (b -> a -> b) -> b ->U1 a -> bSource# foldl' :: (b -> a -> b) -> b ->U1 a -> bSource# foldr1 :: (a -> a -> a) ->U1 a -> aSource# foldl1 :: (a -> a -> a) ->U1 a -> aSource# elem ::Eq a => a ->U1 a ->BoolSource# maximum ::Ord a =>U1 a -> aSource# minimum ::Ord a =>U1 a -> aSource# | |
| Traversable (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| MonadPlus (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Alternative (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| MonadZip (U1 ::Type ->Type)Source# | Since: 4.9.0.0 |
| Contravariant (U1 ::Type ->Type)Source# | |
| Eq (U1 p)Source# | Since: 4.9.0.0 |
| Data p =>Data (U1 p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->U1 p -> c (U1 p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (U1 p)Source# toConstr ::U1 p ->ConstrSource# dataTypeOf ::U1 p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (U1 p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (U1 p))Source# gmapT :: (forall b.Data b => b -> b) ->U1 p ->U1 pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->U1 p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->U1 p -> rSource# gmapQ :: (forall d.Data d => d -> u) ->U1 p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->U1 p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->U1 p -> m (U1 p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->U1 p -> m (U1 p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->U1 p -> m (U1 p)Source# | |
| Ord (U1 p)Source# | Since: 4.7.0.0 |
| Read (U1 p)Source# | Since: 4.9.0.0 |
| Show (U1 p)Source# | Since: 4.9.0.0 |
| Generic (U1 p)Source# | |
| Semigroup (U1 p)Source# | Since: 4.12.0.0 |
| Monoid (U1 p)Source# | Since: 4.12.0.0 |
| typeRep1 (U1 :: k ->Type)Source# | Since: 4.9.0.0 |
| typeRep (U1 p)Source# | Since: 4.7.0.0 |
Used for marking occurrences of the parameter
| MonadPar1Source# | Since: 4.9.0.0 |
| FunctorPar1Source# | Since: 4.9.0.0 |
| MonadFixPar1Source# | Since: 4.9.0.0 |
| ApplicativePar1Source# | Since: 4.9.0.0 |
| FoldablePar1Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Par1 m -> mSource# foldMap ::Monoid m => (a -> m) ->Par1 a -> mSource# foldr :: (a -> b -> b) -> b ->Par1 a -> bSource# foldr' :: (a -> b -> b) -> b ->Par1 a -> bSource# foldl :: (b -> a -> b) -> b ->Par1 a -> bSource# foldl' :: (b -> a -> b) -> b ->Par1 a -> bSource# foldr1 :: (a -> a -> a) ->Par1 a -> aSource# foldl1 :: (a -> a -> a) ->Par1 a -> aSource# elem ::Eq a => a ->Par1 a ->BoolSource# maximum ::Ord a =>Par1 a -> aSource# minimum ::Ord a =>Par1 a -> aSource# | |
| TraversablePar1Source# | Since: 4.9.0.0 |
| MonadZipPar1Source# | Since: 4.9.0.0 |
| Eq p =>Eq (Par1 p)Source# | Since: 4.7.0.0 |
| Data p =>Data (Par1 p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Par1 p -> c (Par1 p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Par1 p)Source# toConstr ::Par1 p ->ConstrSource# dataTypeOf ::Par1 p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Par1 p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Par1 p))Source# gmapT :: (forall b.Data b => b -> b) ->Par1 p ->Par1 pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Par1 p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Par1 p -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Par1 p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Par1 p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Par1 p -> m (Par1 p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Par1 p -> m (Par1 p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Par1 p -> m (Par1 p)Source# | |
| Ord p =>Ord (Par1 p)Source# | Since: 4.7.0.0 |
| Read p =>Read (Par1 p)Source# | Since: 4.7.0.0 |
| Show p =>Show (Par1 p)Source# | Since: 4.7.0.0 |
| Generic (Par1 p)Source# | |
| Semigroup p =>Semigroup (Par1 p)Source# | Since: 4.12.0.0 |
| Monoid p =>Monoid (Par1 p)Source# | Since: 4.12.0.0 |
| Generic1Par1Source# | |
| typeRep (Par1 p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep1Par1Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
newtypeRec1 (f :: k ->Type) (p :: k)Source#
Recursive calls of kind* -> * (or kindk -> *, whenPolyKinds is enabled)
| Generic1 (Rec1 f :: k ->Type)Source# | |
| Monad f =>Monad (Rec1 f)Source# | Since: 4.9.0.0 |
| Functor f =>Functor (Rec1 f)Source# | Since: 4.9.0.0 |
| MonadFix f =>MonadFix (Rec1 f)Source# | Since: 4.9.0.0 |
| Applicative f =>Applicative (Rec1 f)Source# | Since: 4.9.0.0 |
| Foldable f =>Foldable (Rec1 f)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Rec1 f m -> mSource# foldMap ::Monoid m => (a -> m) ->Rec1 f a -> mSource# foldr :: (a -> b -> b) -> b ->Rec1 f a -> bSource# foldr' :: (a -> b -> b) -> b ->Rec1 f a -> bSource# foldl :: (b -> a -> b) -> b ->Rec1 f a -> bSource# foldl' :: (b -> a -> b) -> b ->Rec1 f a -> bSource# foldr1 :: (a -> a -> a) ->Rec1 f a -> aSource# foldl1 :: (a -> a -> a) ->Rec1 f a -> aSource# toList ::Rec1 f a -> [a]Source# length ::Rec1 f a ->IntSource# elem ::Eq a => a ->Rec1 f a ->BoolSource# maximum ::Ord a =>Rec1 f a -> aSource# minimum ::Ord a =>Rec1 f a -> aSource# | |
| Traversable f =>Traversable (Rec1 f)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| MonadPlus f =>MonadPlus (Rec1 f)Source# | Since: 4.9.0.0 |
| Alternative f =>Alternative (Rec1 f)Source# | Since: 4.9.0.0 |
| MonadZip f =>MonadZip (Rec1 f)Source# | Since: 4.9.0.0 |
| Contravariant f =>Contravariant (Rec1 f)Source# | |
| Eq (f p) =>Eq (Rec1 f p)Source# | Since: 4.7.0.0 |
| (Data (f p),Typeable f,Data p) =>Data (Rec1 f p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Rec1 f p -> c (Rec1 f p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Rec1 f p)Source# toConstr ::Rec1 f p ->ConstrSource# dataTypeOf ::Rec1 f p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Rec1 f p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Rec1 f p))Source# gmapT :: (forall b.Data b => b -> b) ->Rec1 f p ->Rec1 f pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Rec1 f p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Rec1 f p -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Rec1 f p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Rec1 f p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Rec1 f p -> m (Rec1 f p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Rec1 f p -> m (Rec1 f p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Rec1 f p -> m (Rec1 f p)Source# | |
| Ord (f p) =>Ord (Rec1 f p)Source# | Since: 4.7.0.0 |
| Read (f p) =>Read (Rec1 f p)Source# | Since: 4.7.0.0 |
| Show (f p) =>Show (Rec1 f p)Source# | Since: 4.7.0.0 |
| Generic (Rec1 f p)Source# | |
| Semigroup (f p) =>Semigroup (Rec1 f p)Source# | Since: 4.12.0.0 |
| Monoid (f p) =>Monoid (Rec1 f p)Source# | Since: 4.12.0.0 |
| typeRep1 (Rec1 f :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (Rec1 f p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics | |
newtypeK1 (i ::Type) c (p :: k)Source#
Constants, additional parameters and recursion of kind*
| Generic1 (K1 i c :: k ->Type)Source# | |
| Bifunctor (K1 i ::Type ->Type ->Type)Source# | Since: 4.9.0.0 |
| Bifoldable (K1 i ::Type ->Type ->Type)Source# | Since: 4.10.0.0 |
| Bitraversable (K1 i ::Type ->Type ->Type)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->K1 i a b -> f (K1 i c d)Source# | |
| Functor (K1 i c ::Type ->Type)Source# | Since: 4.9.0.0 |
| Monoid c =>Applicative (K1 i c ::Type ->Type)Source# | Since: 4.12.0.0 |
| Foldable (K1 i c ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>K1 i c m -> mSource# foldMap ::Monoid m => (a -> m) ->K1 i c a -> mSource# foldr :: (a -> b -> b) -> b ->K1 i c a -> bSource# foldr' :: (a -> b -> b) -> b ->K1 i c a -> bSource# foldl :: (b -> a -> b) -> b ->K1 i c a -> bSource# foldl' :: (b -> a -> b) -> b ->K1 i c a -> bSource# foldr1 :: (a -> a -> a) ->K1 i c a -> aSource# foldl1 :: (a -> a -> a) ->K1 i c a -> aSource# toList ::K1 i c a -> [a]Source# length ::K1 i c a ->IntSource# elem ::Eq a => a ->K1 i c a ->BoolSource# maximum ::Ord a =>K1 i c a -> aSource# minimum ::Ord a =>K1 i c a -> aSource# | |
| Traversable (K1 i c ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| Contravariant (K1 i c ::Type ->Type)Source# | |
| Eq c =>Eq (K1 i c p)Source# | Since: 4.7.0.0 |
| (Typeable i,Data p,Data c) =>Data (K1 i c p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) ->K1 i c p -> c0 (K1 i c p)Source# gunfold :: (forall b r.Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (K1 i c p)Source# toConstr ::K1 i c p ->ConstrSource# dataTypeOf ::K1 i c p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c0 (t d)) ->Maybe (c0 (K1 i c p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c0 (t d e)) ->Maybe (c0 (K1 i c p))Source# gmapT :: (forall b.Data b => b -> b) ->K1 i c p ->K1 i c pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->K1 i c p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->K1 i c p -> rSource# gmapQ :: (forall d.Data d => d -> u) ->K1 i c p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->K1 i c p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->K1 i c p -> m (K1 i c p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->K1 i c p -> m (K1 i c p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->K1 i c p -> m (K1 i c p)Source# | |
| Ord c =>Ord (K1 i c p)Source# | Since: 4.7.0.0 |
| Read c =>Read (K1 i c p)Source# | Since: 4.7.0.0 |
| Show c =>Show (K1 i c p)Source# | Since: 4.7.0.0 |
| Generic (K1 i c p)Source# | |
| Semigroup c =>Semigroup (K1 i c p)Source# | Since: 4.12.0.0 |
| Monoid c =>Monoid (K1 i c p)Source# | Since: 4.12.0.0 |
| typeRep1 (K1 i c :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (K1 i c p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics | |
newtypeM1 (i ::Type) (c ::Meta) (f :: k ->Type) (p :: k)Source#
Meta-information (constructor names, etc.)
| Generic1 (M1 i c f :: k ->Type)Source# | |
| Monad f =>Monad (M1 i c f)Source# | Since: 4.9.0.0 |
| Functor f =>Functor (M1 i c f)Source# | Since: 4.9.0.0 |
| MonadFix f =>MonadFix (M1 i c f)Source# | Since: 4.9.0.0 |
| Applicative f =>Applicative (M1 i c f)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| Foldable f =>Foldable (M1 i c f)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>M1 i c f m -> mSource# foldMap ::Monoid m => (a -> m) ->M1 i c f a -> mSource# foldr :: (a -> b -> b) -> b ->M1 i c f a -> bSource# foldr' :: (a -> b -> b) -> b ->M1 i c f a -> bSource# foldl :: (b -> a -> b) -> b ->M1 i c f a -> bSource# foldl' :: (b -> a -> b) -> b ->M1 i c f a -> bSource# foldr1 :: (a -> a -> a) ->M1 i c f a -> aSource# foldl1 :: (a -> a -> a) ->M1 i c f a -> aSource# toList ::M1 i c f a -> [a]Source# null ::M1 i c f a ->BoolSource# length ::M1 i c f a ->IntSource# elem ::Eq a => a ->M1 i c f a ->BoolSource# maximum ::Ord a =>M1 i c f a -> aSource# minimum ::Ord a =>M1 i c f a -> aSource# | |
| Traversable f =>Traversable (M1 i c f)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| MonadPlus f =>MonadPlus (M1 i c f)Source# | Since: 4.9.0.0 |
| Alternative f =>Alternative (M1 i c f)Source# | Since: 4.9.0.0 |
| MonadZip f =>MonadZip (M1 i c f)Source# | Since: 4.9.0.0 |
| Contravariant f =>Contravariant (M1 i c f)Source# | |
| Eq (f p) =>Eq (M1 i c f p)Source# | Since: 4.7.0.0 |
| (Data p,Data (f p),Typeable c,Typeable i,Typeable f) =>Data (M1 i c f p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) ->M1 i c f p -> c0 (M1 i c f p)Source# gunfold :: (forall b r.Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (M1 i c f p)Source# toConstr ::M1 i c f p ->ConstrSource# dataTypeOf ::M1 i c f p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c0 (t d)) ->Maybe (c0 (M1 i c f p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c0 (t d e)) ->Maybe (c0 (M1 i c f p))Source# gmapT :: (forall b.Data b => b -> b) ->M1 i c f p ->M1 i c f pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->M1 i c f p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->M1 i c f p -> rSource# gmapQ :: (forall d.Data d => d -> u) ->M1 i c f p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->M1 i c f p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->M1 i c f p -> m (M1 i c f p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->M1 i c f p -> m (M1 i c f p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->M1 i c f p -> m (M1 i c f p)Source# | |
| Ord (f p) =>Ord (M1 i c f p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics | |
| Read (f p) =>Read (M1 i c f p)Source# | Since: 4.7.0.0 |
| Show (f p) =>Show (M1 i c f p)Source# | Since: 4.7.0.0 |
| Generic (M1 i c f p)Source# | |
| Semigroup (f p) =>Semigroup (M1 i c f p)Source# | Since: 4.12.0.0 |
| Monoid (f p) =>Monoid (M1 i c f p)Source# | Since: 4.12.0.0 |
| typeRep1 (M1 i c f :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (M1 i c f p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics | |
data ((f :: k ->Type):+: (g :: k ->Type)) (p :: k)infixr 5Source#
Sums: encode choice between constructors
| Generic1 (f:+: g :: k ->Type)Source# | |
| (Functor f,Functor g) =>Functor (f:+: g)Source# | Since: 4.9.0.0 |
| (Foldable f,Foldable g) =>Foldable (f:+: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m => (f:+: g) m -> mSource# foldMap ::Monoid m => (a -> m) -> (f:+: g) a -> mSource# foldr :: (a -> b -> b) -> b -> (f:+: g) a -> bSource# foldr' :: (a -> b -> b) -> b -> (f:+: g) a -> bSource# foldl :: (b -> a -> b) -> b -> (f:+: g) a -> bSource# foldl' :: (b -> a -> b) -> b -> (f:+: g) a -> bSource# foldr1 :: (a -> a -> a) -> (f:+: g) a -> aSource# foldl1 :: (a -> a -> a) -> (f:+: g) a -> aSource# toList :: (f:+: g) a -> [a]Source# null :: (f:+: g) a ->BoolSource# length :: (f:+: g) a ->IntSource# elem ::Eq a => a -> (f:+: g) a ->BoolSource# maximum ::Ord a => (f:+: g) a -> aSource# minimum ::Ord a => (f:+: g) a -> aSource# | |
| (Traversable f,Traversable g) =>Traversable (f:+: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| (Contravariant f,Contravariant g) =>Contravariant (f:+: g)Source# | |
| (Eq (f p),Eq (g p)) =>Eq ((f:+: g) p)Source# | Since: 4.7.0.0 |
| (Typeable f,Typeable g,Data p,Data (f p),Data (g p)) =>Data ((f:+: g) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f:+: g) p -> c ((f:+: g) p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c ((f:+: g) p)Source# toConstr :: (f:+: g) p ->ConstrSource# dataTypeOf :: (f:+: g) p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c ((f:+: g) p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c ((f:+: g) p))Source# gmapT :: (forall b.Data b => b -> b) -> (f:+: g) p -> (f:+: g) pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (f:+: g) p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (f:+: g) p -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (f:+: g) p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (f:+: g) p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (f:+: g) p -> m ((f:+: g) p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (f:+: g) p -> m ((f:+: g) p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (f:+: g) p -> m ((f:+: g) p)Source# | |
| (Ord (f p),Ord (g p)) =>Ord ((f:+: g) p)Source# | Since: 4.7.0.0 |
| (Read (f p),Read (g p)) =>Read ((f:+: g) p)Source# | Since: 4.7.0.0 |
| (Show (f p),Show (g p)) =>Show ((f:+: g) p)Source# | Since: 4.7.0.0 |
| Generic ((f:+: g) p)Source# | |
| typeRep1 (f:+: g :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics typeRep1 (f:+: g :: k ->Type) =D1 (MetaData ":+:" "GHC.Generics" "base"False) (C1 (MetaCons "L1"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec1 f)):+:C1 (MetaCons "R1"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec1 g))) | |
| typeRep ((f:+: g) p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics typeRep ((f:+: g) p) =D1 (MetaData ":+:" "GHC.Generics" "base"False) (C1 (MetaCons "L1"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 (f p))):+:C1 (MetaCons "R1"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 (g p)))) | |
data ((f :: k ->Type):*: (g :: k ->Type)) (p :: k)infixr 6Source#
Products: encode multiple arguments to constructors
Constructors
| (f p):*: (g p)infixr 6 |
| Generic1 (f:*: g :: k ->Type)Source# | |
| (Monad f,Monad g) =>Monad (f:*: g)Source# | Since: 4.9.0.0 |
| (Functor f,Functor g) =>Functor (f:*: g)Source# | Since: 4.9.0.0 |
| (MonadFix f,MonadFix g) =>MonadFix (f:*: g)Source# | Since: 4.9.0.0 |
| (Applicative f,Applicative g) =>Applicative (f:*: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| (Foldable f,Foldable g) =>Foldable (f:*: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m => (f:*: g) m -> mSource# foldMap ::Monoid m => (a -> m) -> (f:*: g) a -> mSource# foldr :: (a -> b -> b) -> b -> (f:*: g) a -> bSource# foldr' :: (a -> b -> b) -> b -> (f:*: g) a -> bSource# foldl :: (b -> a -> b) -> b -> (f:*: g) a -> bSource# foldl' :: (b -> a -> b) -> b -> (f:*: g) a -> bSource# foldr1 :: (a -> a -> a) -> (f:*: g) a -> aSource# foldl1 :: (a -> a -> a) -> (f:*: g) a -> aSource# toList :: (f:*: g) a -> [a]Source# null :: (f:*: g) a ->BoolSource# length :: (f:*: g) a ->IntSource# elem ::Eq a => a -> (f:*: g) a ->BoolSource# maximum ::Ord a => (f:*: g) a -> aSource# minimum ::Ord a => (f:*: g) a -> aSource# | |
| (Traversable f,Traversable g) =>Traversable (f:*: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| (MonadPlus f,MonadPlus g) =>MonadPlus (f:*: g)Source# | Since: 4.9.0.0 |
| (Alternative f,Alternative g) =>Alternative (f:*: g)Source# | Since: 4.9.0.0 |
| (MonadZip f,MonadZip g) =>MonadZip (f:*: g)Source# | Since: 4.9.0.0 |
| (Contravariant f,Contravariant g) =>Contravariant (f:*: g)Source# | |
| (Eq (f p),Eq (g p)) =>Eq ((f:*: g) p)Source# | Since: 4.7.0.0 |
| (Typeable f,Typeable g,Data p,Data (f p),Data (g p)) =>Data ((f:*: g) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f:*: g) p -> c ((f:*: g) p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c ((f:*: g) p)Source# toConstr :: (f:*: g) p ->ConstrSource# dataTypeOf :: (f:*: g) p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c ((f:*: g) p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c ((f:*: g) p))Source# gmapT :: (forall b.Data b => b -> b) -> (f:*: g) p -> (f:*: g) pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (f:*: g) p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (f:*: g) p -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (f:*: g) p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (f:*: g) p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (f:*: g) p -> m ((f:*: g) p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (f:*: g) p -> m ((f:*: g) p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (f:*: g) p -> m ((f:*: g) p)Source# | |
| (Ord (f p),Ord (g p)) =>Ord ((f:*: g) p)Source# | Since: 4.7.0.0 |
| (Read (f p),Read (g p)) =>Read ((f:*: g) p)Source# | Since: 4.7.0.0 |
| (Show (f p),Show (g p)) =>Show ((f:*: g) p)Source# | Since: 4.7.0.0 |
| Generic ((f:*: g) p)Source# | |
| (Semigroup (f p),Semigroup (g p)) =>Semigroup ((f:*: g) p)Source# | Since: 4.12.0.0 |
| (Monoid (f p),Monoid (g p)) =>Monoid ((f:*: g) p)Source# | Since: 4.12.0.0 |
| typeRep1 (f:*: g :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics typeRep1 (f:*: g :: k ->Type) =D1 (MetaData ":*:" "GHC.Generics" "base"False) (C1 (MetaCons ":*:" (InfixIRightAssociative 6)False) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec1 f):*:S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec1 g))) | |
| typeRep ((f:*: g) p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics typeRep ((f:*: g) p) =D1 (MetaData ":*:" "GHC.Generics" "base"False) (C1 (MetaCons ":*:" (InfixIRightAssociative 6)False) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 (f p)):*:S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 (g p)))) | |
newtype ((f :: k2 ->Type):.: (g :: k1 -> k2)) (p :: k1)infixr 7Source#
Composition of functors
| Functor f =>Generic1 (f:.: g :: k ->Type)Source# | |
| (Functor f,Functor g) =>Functor (f:.: g)Source# | Since: 4.9.0.0 |
| (Applicative f,Applicative g) =>Applicative (f:.: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| (Foldable f,Foldable g) =>Foldable (f:.: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m => (f:.: g) m -> mSource# foldMap ::Monoid m => (a -> m) -> (f:.: g) a -> mSource# foldr :: (a -> b -> b) -> b -> (f:.: g) a -> bSource# foldr' :: (a -> b -> b) -> b -> (f:.: g) a -> bSource# foldl :: (b -> a -> b) -> b -> (f:.: g) a -> bSource# foldl' :: (b -> a -> b) -> b -> (f:.: g) a -> bSource# foldr1 :: (a -> a -> a) -> (f:.: g) a -> aSource# foldl1 :: (a -> a -> a) -> (f:.: g) a -> aSource# toList :: (f:.: g) a -> [a]Source# null :: (f:.: g) a ->BoolSource# length :: (f:.: g) a ->IntSource# elem ::Eq a => a -> (f:.: g) a ->BoolSource# maximum ::Ord a => (f:.: g) a -> aSource# minimum ::Ord a => (f:.: g) a -> aSource# | |
| (Traversable f,Traversable g) =>Traversable (f:.: g)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| (Alternative f,Applicative g) =>Alternative (f:.: g)Source# | Since: 4.9.0.0 |
| (Functor f,Contravariant g) =>Contravariant (f:.: g)Source# | |
| Eq (f (g p)) =>Eq ((f:.: g) p)Source# | Since: 4.7.0.0 |
| (Typeable f,Typeable g,Data p,Data (f (g p))) =>Data ((f:.: g) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f:.: g) p -> c ((f:.: g) p)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c ((f:.: g) p)Source# toConstr :: (f:.: g) p ->ConstrSource# dataTypeOf :: (f:.: g) p ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c ((f:.: g) p))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c ((f:.: g) p))Source# gmapT :: (forall b.Data b => b -> b) -> (f:.: g) p -> (f:.: g) pSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (f:.: g) p -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (f:.: g) p -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (f:.: g) p -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (f:.: g) p -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (f:.: g) p -> m ((f:.: g) p)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (f:.: g) p -> m ((f:.: g) p)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (f:.: g) p -> m ((f:.: g) p)Source# | |
| Ord (f (g p)) =>Ord ((f:.: g) p)Source# | Since: 4.7.0.0 |
| Read (f (g p)) =>Read ((f:.: g) p)Source# | Since: 4.7.0.0 |
| Show (f (g p)) =>Show ((f:.: g) p)Source# | Since: 4.7.0.0 |
| Generic ((f:.: g) p)Source# | |
| Semigroup (f (g p)) =>Semigroup ((f:.: g) p)Source# | Since: 4.12.0.0 |
| Monoid (f (g p)) =>Monoid ((f:.: g) p)Source# | Since: 4.12.0.0 |
| typeRep1 (f:.: g :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep ((f:.: g) p)Source# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics | |
data familyURec (a ::Type) (p :: k)Source#
Constants of unlifted kinds
Since: 4.9.0.0
| Generic1 (URecWord :: k ->Type)Source# | |
| Generic1 (URecInt :: k ->Type)Source# | |
| Generic1 (URecFloat :: k ->Type)Source# | |
| Generic1 (URecDouble :: k ->Type)Source# | |
| Generic1 (URecChar :: k ->Type)Source# | |
| Generic1 (URec (Ptr ()) :: k ->Type)Source# | |
| Functor (URecChar ::Type ->Type)Source# | Since: 4.9.0.0 |
| Functor (URecDouble ::Type ->Type)Source# | Since: 4.9.0.0 |
| Functor (URecFloat ::Type ->Type)Source# | Since: 4.9.0.0 |
| Functor (URecInt ::Type ->Type)Source# | Since: 4.9.0.0 |
| Functor (URecWord ::Type ->Type)Source# | Since: 4.9.0.0 |
| Functor (URec (Ptr ()) ::Type ->Type)Source# | Since: 4.9.0.0 |
| Foldable (URecChar ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URecChar m -> mSource# foldMap ::Monoid m => (a -> m) ->URecChar a -> mSource# foldr :: (a -> b -> b) -> b ->URecChar a -> bSource# foldr' :: (a -> b -> b) -> b ->URecChar a -> bSource# foldl :: (b -> a -> b) -> b ->URecChar a -> bSource# foldl' :: (b -> a -> b) -> b ->URecChar a -> bSource# foldr1 :: (a -> a -> a) ->URecChar a -> aSource# foldl1 :: (a -> a -> a) ->URecChar a -> aSource# toList ::URecChar a -> [a]Source# null ::URecChar a ->BoolSource# length ::URecChar a ->IntSource# elem ::Eq a => a ->URecChar a ->BoolSource# maximum ::Ord a =>URecChar a -> aSource# minimum ::Ord a =>URecChar a -> aSource# | |
| Foldable (URecDouble ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URecDouble m -> mSource# foldMap ::Monoid m => (a -> m) ->URecDouble a -> mSource# foldr :: (a -> b -> b) -> b ->URecDouble a -> bSource# foldr' :: (a -> b -> b) -> b ->URecDouble a -> bSource# foldl :: (b -> a -> b) -> b ->URecDouble a -> bSource# foldl' :: (b -> a -> b) -> b ->URecDouble a -> bSource# foldr1 :: (a -> a -> a) ->URecDouble a -> aSource# foldl1 :: (a -> a -> a) ->URecDouble a -> aSource# toList ::URecDouble a -> [a]Source# null ::URecDouble a ->BoolSource# length ::URecDouble a ->IntSource# elem ::Eq a => a ->URecDouble a ->BoolSource# maximum ::Ord a =>URecDouble a -> aSource# minimum ::Ord a =>URecDouble a -> aSource# | |
| Foldable (URecFloat ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URecFloat m -> mSource# foldMap ::Monoid m => (a -> m) ->URecFloat a -> mSource# foldr :: (a -> b -> b) -> b ->URecFloat a -> bSource# foldr' :: (a -> b -> b) -> b ->URecFloat a -> bSource# foldl :: (b -> a -> b) -> b ->URecFloat a -> bSource# foldl' :: (b -> a -> b) -> b ->URecFloat a -> bSource# foldr1 :: (a -> a -> a) ->URecFloat a -> aSource# foldl1 :: (a -> a -> a) ->URecFloat a -> aSource# toList ::URecFloat a -> [a]Source# null ::URecFloat a ->BoolSource# length ::URecFloat a ->IntSource# elem ::Eq a => a ->URecFloat a ->BoolSource# maximum ::Ord a =>URecFloat a -> aSource# minimum ::Ord a =>URecFloat a -> aSource# | |
| Foldable (URecInt ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URecInt m -> mSource# foldMap ::Monoid m => (a -> m) ->URecInt a -> mSource# foldr :: (a -> b -> b) -> b ->URecInt a -> bSource# foldr' :: (a -> b -> b) -> b ->URecInt a -> bSource# foldl :: (b -> a -> b) -> b ->URecInt a -> bSource# foldl' :: (b -> a -> b) -> b ->URecInt a -> bSource# foldr1 :: (a -> a -> a) ->URecInt a -> aSource# foldl1 :: (a -> a -> a) ->URecInt a -> aSource# toList ::URecInt a -> [a]Source# null ::URecInt a ->BoolSource# length ::URecInt a ->IntSource# elem ::Eq a => a ->URecInt a ->BoolSource# maximum ::Ord a =>URecInt a -> aSource# minimum ::Ord a =>URecInt a -> aSource# | |
| Foldable (URecWord ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URecWord m -> mSource# foldMap ::Monoid m => (a -> m) ->URecWord a -> mSource# foldr :: (a -> b -> b) -> b ->URecWord a -> bSource# foldr' :: (a -> b -> b) -> b ->URecWord a -> bSource# foldl :: (b -> a -> b) -> b ->URecWord a -> bSource# foldl' :: (b -> a -> b) -> b ->URecWord a -> bSource# foldr1 :: (a -> a -> a) ->URecWord a -> aSource# foldl1 :: (a -> a -> a) ->URecWord a -> aSource# toList ::URecWord a -> [a]Source# null ::URecWord a ->BoolSource# length ::URecWord a ->IntSource# elem ::Eq a => a ->URecWord a ->BoolSource# maximum ::Ord a =>URecWord a -> aSource# minimum ::Ord a =>URecWord a -> aSource# | |
| Foldable (URec (Ptr ()) ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URec (Ptr ()) m -> mSource# foldMap ::Monoid m => (a -> m) ->URec (Ptr ()) a -> mSource# foldr :: (a -> b -> b) -> b ->URec (Ptr ()) a -> bSource# foldr' :: (a -> b -> b) -> b ->URec (Ptr ()) a -> bSource# foldl :: (b -> a -> b) -> b ->URec (Ptr ()) a -> bSource# foldl' :: (b -> a -> b) -> b ->URec (Ptr ()) a -> bSource# foldr1 :: (a -> a -> a) ->URec (Ptr ()) a -> aSource# foldl1 :: (a -> a -> a) ->URec (Ptr ()) a -> aSource# toList ::URec (Ptr ()) a -> [a]Source# null ::URec (Ptr ()) a ->BoolSource# length ::URec (Ptr ()) a ->IntSource# elem ::Eq a => a ->URec (Ptr ()) a ->BoolSource# maximum ::Ord a =>URec (Ptr ()) a -> aSource# minimum ::Ord a =>URec (Ptr ()) a -> aSource# | |
| Traversable (URecChar ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| Traversable (URecDouble ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| Traversable (URecFloat ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| Traversable (URecInt ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| Traversable (URecWord ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable | |
| Traversable (URec (Ptr ()) ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable Methods traverse ::Applicative f => (a -> f b) ->URec (Ptr ()) a -> f (URec (Ptr ()) b)Source# sequenceA ::Applicative f =>URec (Ptr ()) (f a) -> f (URec (Ptr ()) a)Source# mapM ::Monad m => (a -> m b) ->URec (Ptr ()) a -> m (URec (Ptr ()) b)Source# sequence ::Monad m =>URec (Ptr ()) (m a) -> m (URec (Ptr ()) a)Source# | |
| Eq (URecWord p)Source# | Since: 4.9.0.0 |
| Eq (URecInt p)Source# | Since: 4.9.0.0 |
| Eq (URecFloat p)Source# | |
| Eq (URecDouble p)Source# | Since: 4.9.0.0 |
| Eq (URecChar p)Source# | Since: 4.9.0.0 |
| Eq (URec (Ptr ()) p)Source# | Since: 4.9.0.0 |
| Ord (URecWord p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| Ord (URecInt p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| Ord (URecFloat p)Source# | |
| Ord (URecDouble p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| Ord (URecChar p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| Ord (URec (Ptr ()) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics Methods compare ::URec (Ptr ()) p ->URec (Ptr ()) p ->Ordering# (<) ::URec (Ptr ()) p ->URec (Ptr ()) p ->Bool# (<=) ::URec (Ptr ()) p ->URec (Ptr ()) p ->Bool# (>) ::URec (Ptr ()) p ->URec (Ptr ()) p ->Bool# (>=) ::URec (Ptr ()) p ->URec (Ptr ()) p ->Bool# | |
| Show (URecWord p)Source# | Since: 4.9.0.0 |
| Show (URecInt p)Source# | Since: 4.9.0.0 |
| Show (URecFloat p)Source# | |
| Show (URecDouble p)Source# | Since: 4.9.0.0 |
| Show (URecChar p)Source# | Since: 4.9.0.0 |
| Generic (URecWord p)Source# | |
| Generic (URecInt p)Source# | |
| Generic (URecFloat p)Source# | |
| Generic (URecDouble p)Source# | |
| Generic (URecChar p)Source# | |
| Generic (URec (Ptr ()) p)Source# | |
| dataURecWord (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| dataURecInt (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| dataURecFloat (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| dataURecDouble (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| dataURecChar (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| dataURec (Ptr ()) (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| typeRep1 (URecWord :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep1 (URecInt :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep1 (URecFloat :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep1 (URecDouble :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep1 (URecChar :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep1 (URec (Ptr ()) :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (URecWord p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (URecInt p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (URecFloat p)Source# | |
Instance detailsDefined inGHC.Generics | |
| typeRep (URecDouble p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (URecChar p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (URec (Ptr ()) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
Class for datatypes that represent datatypes
Minimal complete definition
Methods
datatypeName :: t d (f :: k ->Type) (a :: k) -> [Char]Source#
The name of the datatype (unqualified)
moduleName :: t d (f :: k ->Type) (a :: k) -> [Char]Source#
The fully-qualified name of the module where the type is declared
packageName :: t d (f :: k ->Type) (a :: k) -> [Char]Source#
The package name of the module where the type is declared
Since: 4.9.0.0
isNewtype :: t d (f :: k ->Type) (a :: k) ->BoolSource#
Marks if the datatype is actually a newtype
Since: 4.7.0.0
| (KnownSymbol n,KnownSymbol m,KnownSymbol p, SingI nt) =>Datatype (MetaData n m p nt ::Meta)Source# | Since: 4.9.0.0 |
classConstructor cwhereSource#
Class for datatypes that represent data constructors
Minimal complete definition
Methods
conName :: t c (f :: k ->Type) (a :: k) -> [Char]Source#
The name of the constructor
conFixity :: t c (f :: k ->Type) (a :: k) ->FixitySource#
The fixity of the constructor
conIsRecord :: t c (f :: k ->Type) (a :: k) ->BoolSource#
Marks if this constructor is a record
| (KnownSymbol n, SingI f, SingI r) =>Constructor (MetaCons n f r ::Meta)Source# | Since: 4.9.0.0 |
Class for datatypes that represent records
Methods
selName :: t s (f :: k ->Type) (a :: k) -> [Char]Source#
The name of the selector
selSourceUnpackedness :: t s (f :: k ->Type) (a :: k) ->SourceUnpackednessSource#
The selector's unpackedness annotation (if any)
Since: 4.9.0.0
selSourceStrictness :: t s (f :: k ->Type) (a :: k) ->SourceStrictnessSource#
The selector's strictness annotation (if any)
Since: 4.9.0.0
selDecidedStrictness :: t s (f :: k ->Type) (a :: k) ->DecidedStrictnessSource#
The strictness that the compiler inferred for the selector
Since: 4.9.0.0
| (SingI mn, SingI su, SingI ss, SingI ds) =>Selector (MetaSel mn su ss ds ::Meta)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics Methods selName :: t (MetaSel mn su ss ds) f a -> [Char]Source# selSourceUnpackedness :: t (MetaSel mn su ss ds) f a ->SourceUnpackednessSource# selSourceStrictness :: t (MetaSel mn su ss ds) f a ->SourceStrictnessSource# selDecidedStrictness :: t (MetaSel mn su ss ds) f a ->DecidedStrictnessSource# | |
Datatype to represent the fixity of a constructor. An infix | declaration directly corresponds to an application ofInfix.
Constructors
| Prefix | |
| InfixAssociativityInt |
| EqFixitySource# | Since: 4.6.0.0 |
| DataFixitySource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Fixity -> cFixitySource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cFixitySource# toConstr ::Fixity ->ConstrSource# dataTypeOf ::Fixity ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cFixity)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cFixity)Source# gmapT :: (forall b.Data b => b -> b) ->Fixity ->FixitySource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Fixity -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Fixity -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Fixity -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Fixity -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Fixity -> mFixitySource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Fixity -> mFixitySource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Fixity -> mFixitySource# | |
| OrdFixitySource# | Since: 4.6.0.0 |
| ReadFixitySource# | Since: 4.6.0.0 |
| ShowFixitySource# | Since: 4.6.0.0 |
| GenericFixitySource# | |
| typeRepFixitySource# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.Generics typeRepFixity =D1 (MetaData "Fixity" "GHC.Generics" "base"False) (C1 (MetaCons "Prefix"PrefixIFalse) (U1 ::Type ->Type):+:C1 (MetaCons "Infix"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0Associativity):*:S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0Int))) | |
This variant ofFixity appears at the type level.
Since: 4.9.0.0
Constructors
| PrefixI | |
| InfixIAssociativityNat |
Datatype to represent the associativity of a constructor
Constructors
| LeftAssociative | |
| RightAssociative | |
| NotAssociative |
The unpackedness of a field as the user wrote it in the source code. For example, in the following data type:
data E = ExampleConstructor Int {-# NOUNPACK #-} Int {-# UNPACK #-} IntThe fields ofExampleConstructor haveNoSourceUnpackedness,SourceNoUnpack, andSourceUnpack, respectively.
Since: 4.9.0.0
Constructors
| NoSourceUnpackedness | |
| SourceNoUnpack | |
| SourceUnpack |
The strictness of a field as the user wrote it in the source code. For example, in the following data type:
data E = ExampleConstructor Int ~Int !Int
The fields ofExampleConstructor haveNoSourceStrictness,SourceLazy, andSourceStrict, respectively.
Since: 4.9.0.0
Constructors
| NoSourceStrictness | |
| SourceLazy | |
| SourceStrict |
The strictness that GHC infers for a field during compilation. Whereas there are nine different combinations ofSourceUnpackedness andSourceStrictness, the strictness that GHC decides will ultimately be one of lazy, strict, or unpacked. What GHC decides is affected both by what the user writes in the source code and by GHC flags. As an example, consider this data type:
data E = ExampleConstructor {-# UNPACK #-} !Int !Int IntExampleConstructor will haveDecidedStrict,DecidedStrict, andDecidedLazy, respectively.-XStrictData enabled, then the fields will haveDecidedStrict,DecidedStrict, andDecidedStrict, respectively.-O2 enabled, then the fields will haveDecidedUnpack,DecidedStrict, andDecidedLazy, respectively.Since: 4.9.0.0
Constructors
| DecidedLazy | |
| DecidedStrict | |
| DecidedUnpack |
Datatype to represent metadata associated with a datatype (MetaData), constructor (MetaCons), or field selector (MetaSel).
MetaData n m p nt,n is the datatype's name,m is the module in which the datatype is defined,p is the package in which the datatype is defined, andnt is'True if the datatype is anewtype.MetaCons n f s,n is the constructor's name,f is its fixity, ands is'True if the constructor contains record selectors.MetaSel mn su ss ds, if the field uses record syntax, thenmn isJust the record name. Otherwise,mn isNothing.su andss are the field's unpackedness and strictness annotations, andds is the strictness that GHC infers for the field.Since: 4.9.0.0
Constructors
| MetaDataSymbolSymbolSymbolBool | |
| MetaConsSymbolFixityIBool | |
| MetaSel (MaybeSymbol)SourceUnpackednessSourceStrictnessDecidedStrictness |
| (KnownSymbol n, SingI f, SingI r) =>Constructor (MetaCons n f r ::Meta)Source# | Since: 4.9.0.0 |
| (KnownSymbol n,KnownSymbol m,KnownSymbol p, SingI nt) =>Datatype (MetaData n m p nt ::Meta)Source# | Since: 4.9.0.0 |
| (SingI mn, SingI su, SingI ss, SingI ds) =>Selector (MetaSel mn su ss ds ::Meta)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics Methods selName :: t (MetaSel mn su ss ds) f a -> [Char]Source# selSourceUnpackedness :: t (MetaSel mn su ss ds) f a ->SourceUnpackednessSource# selSourceStrictness :: t (MetaSel mn su ss ds) f a ->SourceStrictnessSource# selDecidedStrictness :: t (MetaSel mn su ss ds) f a ->DecidedStrictnessSource# | |
Representable types of kind*. This class is derivable in GHC with theDeriveGeneric flag on.
AGeneric instance must satisfy the following laws:
from.to≡idto.from≡id
Methods
Convert from the datatype to its representation
Convert from the representation to the datatype
classGeneric1 (f :: k ->Type)whereSource#
Representable types of kind* -> * (or kindk -> *, whenPolyKinds is enabled). This class is derivable in GHC with theDeriveGeneric flag on.
AGeneric1 instance must satisfy the following laws:
from1.to1≡idto1.from1≡id
Methods
from1 :: f a ->Rep1 f aSource#
Convert from the datatype to its representation
Convert from the representation to the datatype
Produced byHaddock version 2.20.0