| Copyright | (c) The University of Glasgow CWI 2001--2004 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | experimental |
| Portability | non-portable (local universal quantification) |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Data
Contents
Description
"Scrap your boilerplate" --- Generic programming in Haskell. Seehttp://www.haskell.org/haskellwiki/Research_papers/Generics#Scrap_your_boilerplate.21. This module provides theData class with its primitives for generic programming, along with instances for many datatypes. It corresponds to a merge between the previousData.Generics.Basics and almost all ofData.Generics.Instances. The instances that are not present in this module were moved to theData.Generics.Instances module in thesyb package.
For more information, please visit the new SYB wiki:http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB.
moduleData.Typeable
classTypeable a =>Data awhereSource#
TheData class comprehends a fundamental primitivegfoldl forfolding over constructor applications, say terms. This primitive canbe instantiated in several ways to map over the immediate subtermsof a term; see thegmap combinators later in this class. Indeed, ageneric programmer does not necessarily need to use the ingenious gfoldlprimitive but rather the intuitivegmap combinators. Thegfoldlprimitive is completed by means to query top-level constructors, toturn constructor representations into proper terms, and to list allpossible datatype constructors. This completion allows us to servegeneric programming scenarios like read, show, equality, term generation.
The combinatorsgmapT,gmapQ,gmapM, etc are all provided withdefault definitions in terms ofgfoldl, leaving open the opportunityto provide datatype-specific definitions.(The inclusion of thegmap combinators as members of classDataallows the programmer or the compiler to derive specialised, and maybemore efficient code per datatype.Note:gfoldl is more higher-orderthan thegmap combinators. This is subject to ongoing benchmarkingexperiments. It might turn out that thegmap combinators will bemoved out of the classData.)
Conceptually, the definition of thegmap combinators in terms of theprimitivegfoldl requires the identification of thegfoldl functionarguments. Technically, we also need to identify the type constructorc for the construction of the result type from the folded term type.
In the definition ofgmapQx combinators, we use phantom typeconstructors for thec in the type ofgfoldl because the result typeof a query does not involve the (polymorphic) type of the term argument.In the definition ofgmapQl we simply use the plain constant typeconstructor becausegfoldl is left-associative anyway and so it isreadily suited to fold a left-associative binary operation over theimmediate subterms. In the definition of gmapQr, extra effort isneeded. We use a higher-order accumulation trick to mediate betweenleft-associative constructor application vs. right-associative binaryoperation (e.g.,(:)). When the query is meant to compute a valueof typer, then the result type withing generic folding isr -> r.So the result of folding is a function to which we finally pass theright unit.
With the-XDeriveDataTypeable option, GHC can generate instances of theData class automatically. For example, given the declaration
data T a b = C1 a b | C2 deriving (Typeable, Data)
GHC will generate an instance that is equivalent to
instance (Data a, Data b) => Data (T a b) where gfoldl k z (C1 a b) = z C1 `k` a `k` b gfoldl k z C2 = z C2 gunfold k z c = case constrIndex c of 1 -> k (k (z C1)) 2 -> z C2 toConstr (C1 _ _) = con_C1 toConstr C2 = con_C2 dataTypeOf _ = ty_Tcon_C1 = mkConstr ty_T "C1" [] Prefixcon_C2 = mkConstr ty_T "C2" [] Prefixty_T = mkDataType "Module.T" [con_C1, con_C2]
This is suitable for datatypes that are exported transparently.
Minimal complete definition
Methods
Arguments
| :: (forall d b.Data d => c (d -> b) -> d -> c b) | defines how nonempty constructor applications are folded. It takes the folded tail of the constructor application and its head, i.e., an immediate subterm, and combines them in some way. |
| -> (forall g. g -> c g) | defines how the empty constructor application is folded, like the neutral / start element for list folding. |
| -> a | structure to be folded. |
| -> c a | result, with a type defined in terms of |
Left-associative fold operation for constructor applications.
The type ofgfoldl is a headache, but operationally it is a simple generalisation of a list fold.
The default definition forgfoldl is, which is suitable for abstract datatypes with no substructures.constid
gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c aSource#
Unfolding constructor applications
Obtaining the constructor from a given datum. For proper terms, this is meant to be the top-level constructor. Primitive datatypes are here viewed as potentially infinite sets of values (i.e., constructors).
dataTypeOf :: a ->DataTypeSource#
The outer type constructor of the type
dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c a)Source#
Mediate types and unary type constructors.
InData instances of the form
instance (Data a, ...) => Data (T a)
dataCast1 should be defined asgcast1.
The default definition is, which is appropriate for instances of other forms.constNothing
dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c a)Source#
Mediate types and binary type constructors.
InData instances of the form
instance (Data a, Data b, ...) => Data (T a b)
dataCast2 should be defined asgcast2.
The default definition is, which is appropriate for instances of other forms.constNothing
gmapT :: (forall b.Data b => b -> b) -> a -> aSource#
A generic transformation that maps over the immediate subterms
The default definition instantiates the type constructorc in the type ofgfoldl to an identity datatype constructor, using the isomorphism pair as injection and projection.
gmapQl ::forall r r'. (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> a -> rSource#
A generic query with a left-associative binary operator
gmapQr ::forall r r'. (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> a -> rSource#
A generic query with a right-associative binary operator
gmapQ :: (forall d.Data d => d -> u) -> a -> [u]Source#
A generic query that processes the immediate subterms and returns a list of results. The list is given in the same order as originally specified in the declaration of the data constructors.
gmapQi ::forall u.Int -> (forall d.Data d => d -> u) -> a -> uSource#
A generic query that processes one child by index (zero-based)
gmapM ::forall m.Monad m => (forall d.Data d => d -> m d) -> a -> m aSource#
A generic monadic transformation that maps over the immediate subterms
The default definition instantiates the type constructorc in the type ofgfoldl to the monad datatype constructor, defining injection and projection usingreturn and>>=.
gmapMp ::forall m.MonadPlus m => (forall d.Data d => d -> m d) -> a -> m aSource#
Transformation of at least one immediate subterm does not fail
gmapMo ::forall m.MonadPlus m => (forall d.Data d => d -> m d) -> a -> m aSource#
Transformation of one immediate subterm with success
| DataBoolSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Bool -> cBoolSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cBoolSource# toConstr ::Bool ->ConstrSource# dataTypeOf ::Bool ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cBool)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cBool)Source# gmapT :: (forall b.Data b => b -> b) ->Bool ->BoolSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Bool -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Bool -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Bool -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Bool -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Bool -> mBoolSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Bool -> mBoolSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Bool -> mBoolSource# | |
| DataCharSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Char -> cCharSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cCharSource# toConstr ::Char ->ConstrSource# dataTypeOf ::Char ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cChar)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cChar)Source# gmapT :: (forall b.Data b => b -> b) ->Char ->CharSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Char -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Char -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Char -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Char -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Char -> mCharSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Char -> mCharSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Char -> mCharSource# | |
| DataDoubleSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Double -> cDoubleSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cDoubleSource# toConstr ::Double ->ConstrSource# dataTypeOf ::Double ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cDouble)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cDouble)Source# gmapT :: (forall b.Data b => b -> b) ->Double ->DoubleSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Double -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Double -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Double -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Double -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Double -> mDoubleSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Double -> mDoubleSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Double -> mDoubleSource# | |
| DataFloatSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Float -> cFloatSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cFloatSource# toConstr ::Float ->ConstrSource# dataTypeOf ::Float ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cFloat)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cFloat)Source# gmapT :: (forall b.Data b => b -> b) ->Float ->FloatSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Float -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Float -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Float -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Float -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Float -> mFloatSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Float -> mFloatSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Float -> mFloatSource# | |
| DataIntSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Int -> cIntSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cIntSource# toConstr ::Int ->ConstrSource# dataTypeOf ::Int ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cInt)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cInt)Source# gmapT :: (forall b.Data b => b -> b) ->Int ->IntSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Int -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Int -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Int -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Int -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Int -> mIntSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Int -> mIntSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Int -> mIntSource# | |
| DataInt8Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Int8 -> cInt8Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cInt8Source# toConstr ::Int8 ->ConstrSource# dataTypeOf ::Int8 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cInt8)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cInt8)Source# gmapT :: (forall b.Data b => b -> b) ->Int8 ->Int8Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Int8 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Int8 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Int8 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Int8 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Int8 -> mInt8Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Int8 -> mInt8Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Int8 -> mInt8Source# | |
| DataInt16Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Int16 -> cInt16Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cInt16Source# toConstr ::Int16 ->ConstrSource# dataTypeOf ::Int16 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cInt16)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cInt16)Source# gmapT :: (forall b.Data b => b -> b) ->Int16 ->Int16Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Int16 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Int16 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Int16 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Int16 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Int16 -> mInt16Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Int16 -> mInt16Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Int16 -> mInt16Source# | |
| DataInt32Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Int32 -> cInt32Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cInt32Source# toConstr ::Int32 ->ConstrSource# dataTypeOf ::Int32 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cInt32)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cInt32)Source# gmapT :: (forall b.Data b => b -> b) ->Int32 ->Int32Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Int32 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Int32 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Int32 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Int32 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Int32 -> mInt32Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Int32 -> mInt32Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Int32 -> mInt32Source# | |
| DataInt64Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Int64 -> cInt64Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cInt64Source# toConstr ::Int64 ->ConstrSource# dataTypeOf ::Int64 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cInt64)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cInt64)Source# gmapT :: (forall b.Data b => b -> b) ->Int64 ->Int64Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Int64 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Int64 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Int64 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Int64 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Int64 -> mInt64Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Int64 -> mInt64Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Int64 -> mInt64Source# | |
| DataIntegerSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Integer -> cIntegerSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cIntegerSource# toConstr ::Integer ->ConstrSource# dataTypeOf ::Integer ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cInteger)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cInteger)Source# gmapT :: (forall b.Data b => b -> b) ->Integer ->IntegerSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Integer -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Integer -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Integer -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Integer -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Integer -> mIntegerSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Integer -> mIntegerSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Integer -> mIntegerSource# | |
| DataNaturalSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Natural -> cNaturalSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cNaturalSource# toConstr ::Natural ->ConstrSource# dataTypeOf ::Natural ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cNatural)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cNatural)Source# gmapT :: (forall b.Data b => b -> b) ->Natural ->NaturalSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Natural -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Natural -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Natural -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Natural -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Natural -> mNaturalSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Natural -> mNaturalSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Natural -> mNaturalSource# | |
| DataOrderingSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Ordering -> cOrderingSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cOrderingSource# toConstr ::Ordering ->ConstrSource# dataTypeOf ::Ordering ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cOrdering)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cOrdering)Source# gmapT :: (forall b.Data b => b -> b) ->Ordering ->OrderingSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Ordering -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Ordering -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Ordering -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Ordering -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Ordering -> mOrderingSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Ordering -> mOrderingSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Ordering -> mOrderingSource# | |
| DataWordSource# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Word -> cWordSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cWordSource# toConstr ::Word ->ConstrSource# dataTypeOf ::Word ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cWord)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cWord)Source# gmapT :: (forall b.Data b => b -> b) ->Word ->WordSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Word -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Word -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Word -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Word -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Word -> mWordSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Word -> mWordSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Word -> mWordSource# | |
| DataWord8Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Word8 -> cWord8Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cWord8Source# toConstr ::Word8 ->ConstrSource# dataTypeOf ::Word8 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cWord8)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cWord8)Source# gmapT :: (forall b.Data b => b -> b) ->Word8 ->Word8Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Word8 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Word8 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Word8 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Word8 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Word8 -> mWord8Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Word8 -> mWord8Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Word8 -> mWord8Source# | |
| DataWord16Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Word16 -> cWord16Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cWord16Source# toConstr ::Word16 ->ConstrSource# dataTypeOf ::Word16 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cWord16)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cWord16)Source# gmapT :: (forall b.Data b => b -> b) ->Word16 ->Word16Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Word16 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Word16 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Word16 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Word16 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Word16 -> mWord16Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Word16 -> mWord16Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Word16 -> mWord16Source# | |
| DataWord32Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Word32 -> cWord32Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cWord32Source# toConstr ::Word32 ->ConstrSource# dataTypeOf ::Word32 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cWord32)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cWord32)Source# gmapT :: (forall b.Data b => b -> b) ->Word32 ->Word32Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Word32 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Word32 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Word32 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Word32 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Word32 -> mWord32Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Word32 -> mWord32Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Word32 -> mWord32Source# | |
| DataWord64Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Word64 -> cWord64Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cWord64Source# toConstr ::Word64 ->ConstrSource# dataTypeOf ::Word64 ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cWord64)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cWord64)Source# gmapT :: (forall b.Data b => b -> b) ->Word64 ->Word64Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Word64 -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Word64 -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Word64 -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Word64 -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Word64 -> mWord64Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Word64 -> mWord64Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Word64 -> mWord64Source# | |
| Data ()Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> () -> c ()Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c ()Source# toConstr :: () ->ConstrSource# dataTypeOf :: () ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c ())Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c ())Source# gmapT :: (forall b.Data b => b -> b) -> () -> ()Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> () -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> () -> rSource# gmapQ :: (forall d.Data d => d -> u) -> () -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> () -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> () -> m ()Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> () -> m ()Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> () -> m ()Source# | |
| DataIntPtrSource# | Since: 4.11.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->IntPtr -> cIntPtrSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cIntPtrSource# toConstr ::IntPtr ->ConstrSource# dataTypeOf ::IntPtr ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cIntPtr)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cIntPtr)Source# gmapT :: (forall b.Data b => b -> b) ->IntPtr ->IntPtrSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->IntPtr -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->IntPtr -> rSource# gmapQ :: (forall d.Data d => d -> u) ->IntPtr -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->IntPtr -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->IntPtr -> mIntPtrSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->IntPtr -> mIntPtrSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->IntPtr -> mIntPtrSource# | |
| DataWordPtrSource# | Since: 4.11.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->WordPtr -> cWordPtrSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cWordPtrSource# toConstr ::WordPtr ->ConstrSource# dataTypeOf ::WordPtr ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cWordPtr)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cWordPtr)Source# gmapT :: (forall b.Data b => b -> b) ->WordPtr ->WordPtrSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->WordPtr -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->WordPtr -> rSource# gmapQ :: (forall d.Data d => d -> u) ->WordPtr -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->WordPtr -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->WordPtr -> mWordPtrSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->WordPtr -> mWordPtrSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->WordPtr -> mWordPtrSource# | |
| DataDecidedStrictnessSource# | 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) ->DecidedStrictness -> cDecidedStrictnessSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cDecidedStrictnessSource# toConstr ::DecidedStrictness ->ConstrSource# dataTypeOf ::DecidedStrictness ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cDecidedStrictness)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cDecidedStrictness)Source# gmapT :: (forall b.Data b => b -> b) ->DecidedStrictness ->DecidedStrictnessSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->DecidedStrictness -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->DecidedStrictness -> rSource# gmapQ :: (forall d.Data d => d -> u) ->DecidedStrictness -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->DecidedStrictness -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->DecidedStrictness -> mDecidedStrictnessSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->DecidedStrictness -> mDecidedStrictnessSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->DecidedStrictness -> mDecidedStrictnessSource# | |
| DataSourceStrictnessSource# | 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) ->SourceStrictness -> cSourceStrictnessSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cSourceStrictnessSource# toConstr ::SourceStrictness ->ConstrSource# dataTypeOf ::SourceStrictness ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cSourceStrictness)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cSourceStrictness)Source# gmapT :: (forall b.Data b => b -> b) ->SourceStrictness ->SourceStrictnessSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->SourceStrictness -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->SourceStrictness -> rSource# gmapQ :: (forall d.Data d => d -> u) ->SourceStrictness -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->SourceStrictness -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->SourceStrictness -> mSourceStrictnessSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->SourceStrictness -> mSourceStrictnessSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->SourceStrictness -> mSourceStrictnessSource# | |
| DataSourceUnpackednessSource# | 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) ->SourceUnpackedness -> cSourceUnpackednessSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cSourceUnpackednessSource# toConstr ::SourceUnpackedness ->ConstrSource# dataTypeOf ::SourceUnpackedness ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cSourceUnpackedness)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cSourceUnpackedness)Source# gmapT :: (forall b.Data b => b -> b) ->SourceUnpackedness ->SourceUnpackednessSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->SourceUnpackedness -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->SourceUnpackedness -> rSource# gmapQ :: (forall d.Data d => d -> u) ->SourceUnpackedness -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->SourceUnpackedness -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->SourceUnpackedness -> mSourceUnpackednessSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->SourceUnpackedness -> mSourceUnpackednessSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->SourceUnpackedness -> mSourceUnpackednessSource# | |
| DataAssociativitySource# | 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) ->Associativity -> cAssociativitySource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAssociativitySource# toConstr ::Associativity ->ConstrSource# dataTypeOf ::Associativity ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAssociativity)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAssociativity)Source# gmapT :: (forall b.Data b => b -> b) ->Associativity ->AssociativitySource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Associativity -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Associativity -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Associativity -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Associativity -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Associativity -> mAssociativitySource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Associativity -> mAssociativitySource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Associativity -> mAssociativitySource# | |
| 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# | |
| DataAnySource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Any -> cAnySource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAnySource# toConstr ::Any ->ConstrSource# dataTypeOf ::Any ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAny)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAny)Source# gmapT :: (forall b.Data b => b -> b) ->Any ->AnySource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Any -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Any -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Any -> mAnySource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource# | |
| DataAllSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->All -> cAllSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAllSource# toConstr ::All ->ConstrSource# dataTypeOf ::All ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAll)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAll)Source# gmapT :: (forall b.Data b => b -> b) ->All ->AllSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource# gmapQ :: (forall d.Data d => d -> u) ->All -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->All -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->All -> mAllSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource# | |
| DataVersionSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Version -> cVersionSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cVersionSource# toConstr ::Version ->ConstrSource# dataTypeOf ::Version ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cVersion)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cVersion)Source# gmapT :: (forall b.Data b => b -> b) ->Version ->VersionSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Version -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Version -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Version -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Version -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Version -> mVersionSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Version -> mVersionSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Version -> mVersionSource# | |
| DataSpecConstrAnnotationSource# | Since: 4.3.0.0 |
Instance detailsDefined inGHC.Exts Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->SpecConstrAnnotation -> cSpecConstrAnnotationSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cSpecConstrAnnotationSource# toConstr ::SpecConstrAnnotation ->ConstrSource# dataTypeOf ::SpecConstrAnnotation ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cSpecConstrAnnotation)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cSpecConstrAnnotation)Source# gmapT :: (forall b.Data b => b -> b) ->SpecConstrAnnotation ->SpecConstrAnnotationSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->SpecConstrAnnotation -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->SpecConstrAnnotation -> rSource# gmapQ :: (forall d.Data d => d -> u) ->SpecConstrAnnotation -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->SpecConstrAnnotation -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->SpecConstrAnnotation -> mSpecConstrAnnotationSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->SpecConstrAnnotation -> mSpecConstrAnnotationSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->SpecConstrAnnotation -> mSpecConstrAnnotationSource# | |
| DataVoidSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Void Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Void -> cVoidSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cVoidSource# toConstr ::Void ->ConstrSource# dataTypeOf ::Void ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cVoid)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cVoid)Source# gmapT :: (forall b.Data b => b -> b) ->Void ->VoidSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Void -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Void -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Void -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Void -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Void -> mVoidSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Void -> mVoidSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Void -> mVoidSource# | |
| Data a =>Data [a]Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> [a] -> c [a]Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c [a]Source# toConstr :: [a] ->ConstrSource# dataTypeOf :: [a] ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c [a])Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c [a])Source# gmapT :: (forall b.Data b => b -> b) -> [a] -> [a]Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> [a] -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> [a] -> rSource# gmapQ :: (forall d.Data d => d -> u) -> [a] -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> [a] -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> [a] -> m [a]Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> [a] -> m [a]Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> [a] -> m [a]Source# | |
| Data a =>Data (Maybe a)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Maybe a -> c (Maybe a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Maybe a)Source# toConstr ::Maybe a ->ConstrSource# dataTypeOf ::Maybe a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Maybe a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Maybe a))Source# gmapT :: (forall b.Data b => b -> b) ->Maybe a ->Maybe aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Maybe a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Maybe a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Maybe a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Maybe a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Maybe a -> m (Maybe a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Maybe a -> m (Maybe a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Maybe a -> m (Maybe a)Source# | |
| (Data a,Integral a) =>Data (Ratio a)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Ratio a -> c (Ratio a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Ratio a)Source# toConstr ::Ratio a ->ConstrSource# dataTypeOf ::Ratio a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Ratio a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Ratio a))Source# gmapT :: (forall b.Data b => b -> b) ->Ratio a ->Ratio aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Ratio a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Ratio a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Ratio a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Ratio a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Ratio a -> m (Ratio a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Ratio a -> m (Ratio a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Ratio a -> m (Ratio a)Source# | |
| Data a =>Data (Ptr a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Ptr a -> c (Ptr a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Ptr a)Source# toConstr ::Ptr a ->ConstrSource# dataTypeOf ::Ptr a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Ptr a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Ptr a))Source# gmapT :: (forall b.Data b => b -> b) ->Ptr a ->Ptr aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Ptr a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Ptr a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Ptr a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Ptr a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Ptr a -> m (Ptr a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Ptr a -> m (Ptr a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Ptr a -> m (Ptr a)Source# | |
| 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# | |
| Data a =>Data (NonEmpty a)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) ->NonEmpty a -> c (NonEmpty a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (NonEmpty a)Source# toConstr ::NonEmpty a ->ConstrSource# dataTypeOf ::NonEmpty a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (NonEmpty a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (NonEmpty a))Source# gmapT :: (forall b.Data b => b -> b) ->NonEmpty a ->NonEmpty aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->NonEmpty a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->NonEmpty a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->NonEmpty a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->NonEmpty a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->NonEmpty a -> m (NonEmpty a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->NonEmpty a -> m (NonEmpty a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->NonEmpty a -> m (NonEmpty a)Source# | |
| Data a =>Data (Down a)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Down a -> c (Down a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Down a)Source# toConstr ::Down a ->ConstrSource# dataTypeOf ::Down a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Down a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Down a))Source# gmapT :: (forall b.Data b => b -> b) ->Down a ->Down aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Down a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Down a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Down a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Down a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Down a -> m (Down a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Down a -> m (Down a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Down a -> m (Down a)Source# | |
| Data a =>Data (Product a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Product a -> c (Product a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Product a)Source# toConstr ::Product a ->ConstrSource# dataTypeOf ::Product a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Product a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Product a))Source# gmapT :: (forall b.Data b => b -> b) ->Product a ->Product aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Product a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Product a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source# | |
| Data a =>Data (Sum a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Sum a -> c (Sum a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Sum a)Source# toConstr ::Sum a ->ConstrSource# dataTypeOf ::Sum a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Sum a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Sum a))Source# gmapT :: (forall b.Data b => b -> b) ->Sum a ->Sum aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Sum a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Sum a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source# | |
| Data a =>Data (Dual a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Dual a -> c (Dual a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Dual a)Source# toConstr ::Dual a ->ConstrSource# dataTypeOf ::Dual a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Dual a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Dual a))Source# gmapT :: (forall b.Data b => b -> b) ->Dual a ->Dual aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Dual a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Dual a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source# | |
| Data a =>Data (Last a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Last a -> c (Last a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Last a)Source# toConstr ::Last a ->ConstrSource# dataTypeOf ::Last a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Last a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Last a))Source# gmapT :: (forall b.Data b => b -> b) ->Last a ->Last aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Last a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Last a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# | |
| Data a =>Data (First a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->First a -> c (First a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (First a)Source# toConstr ::First a ->ConstrSource# dataTypeOf ::First a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (First a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (First a))Source# gmapT :: (forall b.Data b => b -> b) ->First a ->First aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->First a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->First a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# | |
| Data a =>Data (ForeignPtr a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->ForeignPtr a -> c (ForeignPtr a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (ForeignPtr a)Source# toConstr ::ForeignPtr a ->ConstrSource# dataTypeOf ::ForeignPtr a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (ForeignPtr a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (ForeignPtr a))Source# gmapT :: (forall b.Data b => b -> b) ->ForeignPtr a ->ForeignPtr aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->ForeignPtr a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->ForeignPtr a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->ForeignPtr a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->ForeignPtr a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->ForeignPtr a -> m (ForeignPtr a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->ForeignPtr a -> m (ForeignPtr a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->ForeignPtr a -> m (ForeignPtr a)Source# | |
| Data a =>Data (Identity a)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) ->Identity a -> c (Identity a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Identity a)Source# toConstr ::Identity a ->ConstrSource# dataTypeOf ::Identity a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Identity a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Identity a))Source# gmapT :: (forall b.Data b => b -> b) ->Identity a ->Identity aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Identity a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Identity a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Identity a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Identity a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Identity a -> m (Identity a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Identity a -> m (Identity a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Identity a -> m (Identity a)Source# | |
| Data a =>Data (Option a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Option a -> c (Option a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Option a)Source# toConstr ::Option a ->ConstrSource# dataTypeOf ::Option a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Option a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Option a))Source# gmapT :: (forall b.Data b => b -> b) ->Option a ->Option aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Option a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Option a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Option a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Option a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source# | |
| Data m =>Data (WrappedMonoid m)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->WrappedMonoid m -> c (WrappedMonoid m)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (WrappedMonoid m)Source# toConstr ::WrappedMonoid m ->ConstrSource# dataTypeOf ::WrappedMonoid m ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (WrappedMonoid m))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (WrappedMonoid m))Source# gmapT :: (forall b.Data b => b -> b) ->WrappedMonoid m ->WrappedMonoid mSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->WrappedMonoid m -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->WrappedMonoid m -> rSource# gmapQ :: (forall d.Data d => d -> u) ->WrappedMonoid m -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->WrappedMonoid m -> uSource# gmapM ::Monad m0 => (forall d.Data d => d -> m0 d) ->WrappedMonoid m -> m0 (WrappedMonoid m)Source# gmapMp ::MonadPlus m0 => (forall d.Data d => d -> m0 d) ->WrappedMonoid m -> m0 (WrappedMonoid m)Source# gmapMo ::MonadPlus m0 => (forall d.Data d => d -> m0 d) ->WrappedMonoid m -> m0 (WrappedMonoid m)Source# | |
| Data a =>Data (Last a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Last a -> c (Last a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Last a)Source# toConstr ::Last a ->ConstrSource# dataTypeOf ::Last a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Last a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Last a))Source# gmapT :: (forall b.Data b => b -> b) ->Last a ->Last aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Last a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Last a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# | |
| Data a =>Data (First a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->First a -> c (First a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (First a)Source# toConstr ::First a ->ConstrSource# dataTypeOf ::First a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (First a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (First a))Source# gmapT :: (forall b.Data b => b -> b) ->First a ->First aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->First a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->First a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# | |
| Data a =>Data (Max a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Max a -> c (Max a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Max a)Source# toConstr ::Max a ->ConstrSource# dataTypeOf ::Max a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Max a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Max a))Source# gmapT :: (forall b.Data b => b -> b) ->Max a ->Max aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Max a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Max a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Max a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Max a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Max a -> m (Max a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Max a -> m (Max a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Max a -> m (Max a)Source# | |
| Data a =>Data (Min a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Min a -> c (Min a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Min a)Source# toConstr ::Min a ->ConstrSource# dataTypeOf ::Min a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Min a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Min a))Source# gmapT :: (forall b.Data b => b -> b) ->Min a ->Min aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Min a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Min a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Min a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Min a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Min a -> m (Min a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Min a -> m (Min a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Min a -> m (Min a)Source# | |
| Typeable a =>Data (Fixed a)Source# | Since: 4.1.0.0 |
Instance detailsDefined inData.Fixed Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Fixed a -> c (Fixed a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Fixed a)Source# toConstr ::Fixed a ->ConstrSource# dataTypeOf ::Fixed a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Fixed a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Fixed a))Source# gmapT :: (forall b.Data b => b -> b) ->Fixed a ->Fixed aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Fixed a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Fixed a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Fixed a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Fixed a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Fixed a -> m (Fixed a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Fixed a -> m (Fixed a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Fixed a -> m (Fixed a)Source# | |
| Data a =>Data (Complex a)Source# | Since: 2.1 |
Instance detailsDefined inData.Complex Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Complex a -> c (Complex a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Complex a)Source# toConstr ::Complex a ->ConstrSource# dataTypeOf ::Complex a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Complex a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Complex a))Source# gmapT :: (forall b.Data b => b -> b) ->Complex a ->Complex aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Complex a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Complex a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Complex a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Complex a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Complex a -> m (Complex a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Complex a -> m (Complex a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Complex a -> m (Complex a)Source# | |
| (Data a,Data b) =>Data (Either a b)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) ->Either a b -> c (Either a b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Either a b)Source# toConstr ::Either a b ->ConstrSource# dataTypeOf ::Either a b ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Either a b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Either a b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) ->Either a b ->Either a bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Either a b -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Either a b -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Either a b -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Either a b -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Either a b -> m (Either a b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Either a b -> m (Either a b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Either a b -> m (Either a b)Source# | |
| 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# | |
| 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# | |
| (Data a,Data b) =>Data (a, b)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a, b) -> c (a, b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (a, b)Source# toConstr :: (a, b) ->ConstrSource# dataTypeOf :: (a, b) ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (a, b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (a, b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a, b) -> (a, b)Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (a, b) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (a, b) -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (a, b) -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (a, b) -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (a, b) -> m (a, b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (a, b) -> m (a, b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (a, b) -> m (a, b)Source# | |
| Data t =>Data (Proxy t)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Proxy t -> c (Proxy t)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Proxy t)Source# toConstr ::Proxy t ->ConstrSource# dataTypeOf ::Proxy t ->DataTypeSource# dataCast1 ::Typeable t0 => (forall d.Data d => c (t0 d)) ->Maybe (c (Proxy t))Source# dataCast2 ::Typeable t0 => (forall d e. (Data d,Data e) => c (t0 d e)) ->Maybe (c (Proxy t))Source# gmapT :: (forall b.Data b => b -> b) ->Proxy t ->Proxy tSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Proxy t -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Proxy t -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Proxy t -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Proxy t -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Proxy t -> m (Proxy t)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Proxy t -> m (Proxy t)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Proxy t -> m (Proxy t)Source# | |
| (Data a,Data b) =>Data (Arg a b)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) ->Arg a b -> c (Arg a b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Arg a b)Source# toConstr ::Arg a b ->ConstrSource# dataTypeOf ::Arg a b ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Arg a b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Arg a b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) ->Arg a b ->Arg a bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Arg a b -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Arg a b -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Arg a b -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Arg a b -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Arg a b -> m (Arg a b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Arg a b -> m (Arg a b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Arg a b -> m (Arg a b)Source# | |
| (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# | |
| (Data a,Data b,Data c) =>Data (a, b, c)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c0 (d -> b0) -> d -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c) -> c0 (a, b, c)Source# gunfold :: (forall b0 r.Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (a, b, c)Source# toConstr :: (a, b, c) ->ConstrSource# dataTypeOf :: (a, b, c) ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c0 (t d)) ->Maybe (c0 (a, b, c))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c0 (t d e)) ->Maybe (c0 (a, b, c))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a, b, c) -> (a, b, c)Source# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (a, b, c) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (a, b, c) -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (a, b, c) -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (a, b, c) -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (a, b, c) -> m (a, b, c)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (a, b, c) -> m (a, b, c)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (a, b, c) -> m (a, b, c)Source# | |
| (a ~ b,Data a) =>Data (a:~: b)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a:~: b) -> c (a:~: b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (a:~: b)Source# toConstr :: (a:~: b) ->ConstrSource# dataTypeOf :: (a:~: b) ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (a:~: b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (a:~: b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a:~: b) -> a:~: bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (a:~: b) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (a:~: b) -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (a:~: b) -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (a:~: b) -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (a:~: b) -> m (a:~: b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (a:~: b) -> m (a:~: b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (a:~: b) -> m (a:~: b)Source# | |
| (Coercible a b,Data a,Data b) =>Data (Coercion a b)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) ->Coercion a b -> c (Coercion a b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Coercion a b)Source# toConstr ::Coercion a b ->ConstrSource# dataTypeOf ::Coercion a b ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Coercion a b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Coercion a b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) ->Coercion a b ->Coercion a bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Coercion a b -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Coercion a b -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Coercion a b -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Coercion a b -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Coercion a b -> m (Coercion a b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Coercion a b -> m (Coercion a b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Coercion a b -> m (Coercion a b)Source# | |
| (Data (f a),Data a,Typeable f) =>Data (Alt f a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Alt f a -> c (Alt f a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Alt f a)Source# toConstr ::Alt f a ->ConstrSource# dataTypeOf ::Alt f a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Alt f a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Alt f a))Source# gmapT :: (forall b.Data b => b -> b) ->Alt f a ->Alt f aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Alt f a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Alt f a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Alt f a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Alt f a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Alt f a -> m (Alt f a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Alt f a -> m (Alt f a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Alt f a -> m (Alt f a)Source# | |
| (Data (f a),Data a,Typeable f) =>Data (Ap f a)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Ap f a -> c (Ap f a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Ap f a)Source# toConstr ::Ap f a ->ConstrSource# dataTypeOf ::Ap f a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Ap f a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Ap f a))Source# gmapT :: (forall b.Data b => b -> b) ->Ap f a ->Ap f aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Ap f a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Ap f a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Ap f a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Ap f a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Ap f a -> m (Ap f a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Ap f a -> m (Ap f a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Ap f a -> m (Ap f a)Source# | |
| (Typeable k,Data a,Typeable b) =>Data (Const a b)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) ->Const a b -> c (Const a b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Const a b)Source# toConstr ::Const a b ->ConstrSource# dataTypeOf ::Const a b ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Const a b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Const a b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) ->Const a b ->Const a bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Const a b -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Const a b -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Const a b -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Const a b -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Const a b -> m (Const a b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Const a b -> m (Const a b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Const a b -> m (Const a b)Source# | |
| (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# | |
| (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# | |
| (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# | |
| (Data a,Data b,Data c,Data d) =>Data (a, b, c, d)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d0 b0.Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d) -> c0 (a, b, c, d)Source# gunfold :: (forall b0 r.Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (a, b, c, d)Source# toConstr :: (a, b, c, d) ->ConstrSource# dataTypeOf :: (a, b, c, d) ->DataTypeSource# dataCast1 ::Typeable t => (forall d0.Data d0 => c0 (t d0)) ->Maybe (c0 (a, b, c, d))Source# dataCast2 ::Typeable t => (forall d0 e. (Data d0,Data e) => c0 (t d0 e)) ->Maybe (c0 (a, b, c, d))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a, b, c, d) -> (a, b, c, d)Source# gmapQl :: (r -> r' -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d) -> rSource# gmapQ :: (forall d0.Data d0 => d0 -> u) -> (a, b, c, d) -> [u]Source# gmapQi ::Int -> (forall d0.Data d0 => d0 -> u) -> (a, b, c, d) -> uSource# gmapM ::Monad m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d)Source# gmapMp ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d)Source# gmapMo ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d)Source# | |
| (Typeable i,Typeable j,Typeable a,Typeable b, a~~ b) =>Data (a:~~: b)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a:~~: b) -> c (a:~~: b)Source# gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (a:~~: b)Source# toConstr :: (a:~~: b) ->ConstrSource# dataTypeOf :: (a:~~: b) ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (a:~~: b))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (a:~~: b))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a:~~: b) -> a:~~: bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (a:~~: b) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (a:~~: b) -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (a:~~: b) -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (a:~~: b) -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) -> (a:~~: b) -> m (a:~~: b)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) -> (a:~~: b) -> m (a:~~: b)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) -> (a:~~: b) -> m (a:~~: b)Source# | |
| (Typeable a,Typeable f,Typeable g,Typeable k,Data (f a),Data (g a)) =>Data (Sum f g a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Sum Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) ->Sum f g a -> c (Sum f g a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Sum f g a)Source# toConstr ::Sum f g a ->ConstrSource# dataTypeOf ::Sum f g a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Sum f g a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Sum f g a))Source# gmapT :: (forall b.Data b => b -> b) ->Sum f g a ->Sum f g aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Sum f g a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Sum f g a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Sum f g a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Sum f g a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Sum f g a -> m (Sum f g a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum f g a -> m (Sum f g a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum f g a -> m (Sum f g a)Source# | |
| (Typeable a,Typeable f,Typeable g,Typeable k,Data (f a),Data (g a)) =>Data (Product f g a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Product Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) ->Product f g a -> c (Product f g a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Product f g a)Source# toConstr ::Product f g a ->ConstrSource# dataTypeOf ::Product f g a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Product f g a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Product f g a))Source# gmapT :: (forall b.Data b => b -> b) ->Product f g a ->Product f g aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Product f g a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Product f g a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Product f g a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Product f g a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Product f g a -> m (Product f g a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Product f g a -> m (Product f g a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Product f g a -> m (Product f g a)Source# | |
| (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# | |
| (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# | |
| (Data a,Data b,Data c,Data d,Data e) =>Data (a, b, c, d, e)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d0 b0.Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d, e) -> c0 (a, b, c, d, e)Source# gunfold :: (forall b0 r.Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (a, b, c, d, e)Source# toConstr :: (a, b, c, d, e) ->ConstrSource# dataTypeOf :: (a, b, c, d, e) ->DataTypeSource# dataCast1 ::Typeable t => (forall d0.Data d0 => c0 (t d0)) ->Maybe (c0 (a, b, c, d, e))Source# dataCast2 ::Typeable t => (forall d0 e0. (Data d0,Data e0) => c0 (t d0 e0)) ->Maybe (c0 (a, b, c, d, e))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a, b, c, d, e) -> (a, b, c, d, e)Source# gmapQl :: (r -> r' -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d, e) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d, e) -> rSource# gmapQ :: (forall d0.Data d0 => d0 -> u) -> (a, b, c, d, e) -> [u]Source# gmapQi ::Int -> (forall d0.Data d0 => d0 -> u) -> (a, b, c, d, e) -> uSource# gmapM ::Monad m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e)Source# gmapMp ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e)Source# gmapMo ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e)Source# | |
| (Typeable a,Typeable f,Typeable g,Typeable k1,Typeable k2,Data (f (g a))) =>Data (Compose f g a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Compose Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) ->Compose f g a -> c (Compose f g a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Compose f g a)Source# toConstr ::Compose f g a ->ConstrSource# dataTypeOf ::Compose f g a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Compose f g a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Compose f g a))Source# gmapT :: (forall b.Data b => b -> b) ->Compose f g a ->Compose f g aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Compose f g a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Compose f g a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Compose f g a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Compose f g a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Compose f g a -> m (Compose f g a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Compose f g a -> m (Compose f g a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Compose f g a -> m (Compose f g a)Source# | |
| (Data a,Data b,Data c,Data d,Data e,Data f) =>Data (a, b, c, d, e, f)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d0 b0.Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d, e, f) -> c0 (a, b, c, d, e, f)Source# gunfold :: (forall b0 r.Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (a, b, c, d, e, f)Source# toConstr :: (a, b, c, d, e, f) ->ConstrSource# dataTypeOf :: (a, b, c, d, e, f) ->DataTypeSource# dataCast1 ::Typeable t => (forall d0.Data d0 => c0 (t d0)) ->Maybe (c0 (a, b, c, d, e, f))Source# dataCast2 ::Typeable t => (forall d0 e0. (Data d0,Data e0) => c0 (t d0 e0)) ->Maybe (c0 (a, b, c, d, e, f))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f)Source# gmapQl :: (r -> r' -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d, e, f) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d, e, f) -> rSource# gmapQ :: (forall d0.Data d0 => d0 -> u) -> (a, b, c, d, e, f) -> [u]Source# gmapQi ::Int -> (forall d0.Data d0 => d0 -> u) -> (a, b, c, d, e, f) -> uSource# gmapM ::Monad m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f)Source# gmapMp ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f)Source# gmapMo ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f)Source# | |
| (Data a,Data b,Data c,Data d,Data e,Data f,Data g) =>Data (a, b, c, d, e, f, g)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d0 b0.Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g0. g0 -> c0 g0) -> (a, b, c, d, e, f, g) -> c0 (a, b, c, d, e, f, g)Source# gunfold :: (forall b0 r.Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) ->Constr -> c0 (a, b, c, d, e, f, g)Source# toConstr :: (a, b, c, d, e, f, g) ->ConstrSource# dataTypeOf :: (a, b, c, d, e, f, g) ->DataTypeSource# dataCast1 ::Typeable t => (forall d0.Data d0 => c0 (t d0)) ->Maybe (c0 (a, b, c, d, e, f, g))Source# dataCast2 ::Typeable t => (forall d0 e0. (Data d0,Data e0) => c0 (t d0 e0)) ->Maybe (c0 (a, b, c, d, e, f, g))Source# gmapT :: (forall b0.Data b0 => b0 -> b0) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g)Source# gmapQl :: (r -> r' -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d, e, f, g) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d0.Data d0 => d0 -> r') -> (a, b, c, d, e, f, g) -> rSource# gmapQ :: (forall d0.Data d0 => d0 -> u) -> (a, b, c, d, e, f, g) -> [u]Source# gmapQi ::Int -> (forall d0.Data d0 => d0 -> u) -> (a, b, c, d, e, f, g) -> uSource# gmapM ::Monad m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g)Source# gmapMp ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g)Source# gmapMo ::MonadPlus m => (forall d0.Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g)Source# | |
Representation of datatypes. A package of constructor representations with names of type and module.
mkNoRepType ::String ->DataTypeSource#
Constructs a non-representation for a non-representable type
dataTypeName ::DataType ->StringSource#
Gets the type constructor including the module
Public representation of datatypes
dataTypeRep ::DataType ->DataRepSource#
Gets the public presentation of a datatype
dataTypeConstrs ::DataType -> [Constr]Source#
Gets the constructors of an algebraic datatype
indexConstr ::DataType ->ConIndex ->ConstrSource#
Gets the constructor for an index (algebraic datatypes only)
maxConstrIndex ::DataType ->ConIndexSource#
Gets the maximum constructor index of an algebraic datatype
isNorepType ::DataType ->BoolSource#
Test for a non-representable type
Representation of constructors. Note that equality on constructors with different types may not work -- i.e. the constructors forFalse andNothing may compare equal.
Unique index for datatype constructors, counting from 1 in the order they are given in the program text.
constrType ::Constr ->DataTypeSource#
Gets the datatype of a constructor
Public representation of constructors
constrFields ::Constr -> [String]Source#
Gets the field labels of a constructor. The list of labels is returned in the same order as they were given in the original constructor declaration.
constrFixity ::Constr ->FixitySource#
Gets the fixity of a constructor
constrIndex ::Constr ->ConIndexSource#
Gets the index of a constructor (algebraic datatypes only)
showConstr ::Constr ->StringSource#
Gets the string for a constructor
tyconUQname ::String ->StringSource#
Gets the unqualified type constructor: drop *.*.*... before name
tyconModule ::String ->StringSource#
Gets the module of a type constructor: take *.*.*... before name
gunfoldfromConstr ::Data a =>Constr -> aSource#
Build a term skeleton
fromConstrB ::Data a => (forall d.Data d => d) ->Constr -> aSource#
Build a term and use a generic function for subterms
fromConstrM ::forall m a. (Monad m,Data a) => (forall d.Data d => m d) ->Constr -> m aSource#
Monadic variation onfromConstrB
Produced byHaddock version 2.20.0