Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- class Typeable (a :: k)
- data TyCon
- typeOf7 :: Typeable t => t a b c d e f g -> TypeRep
- typeOf6 :: Typeable t => t a b c d e f -> TypeRep
- typeOf5 :: Typeable t => t a b c d e -> TypeRep
- typeOf4 :: Typeable t => t a b c d -> TypeRep
- typeOf3 :: Typeable t => t a b c -> TypeRep
- typeOf2 :: Typeable t => t a b -> TypeRep
- typeOf1 :: Typeable t => t a -> TypeRep
- rnfTypeRep :: TypeRep -> ()
- typeRepFingerprint :: TypeRep -> Fingerprint
- typeRepTyCon :: TypeRep -> TyCon
- typeRepArgs :: TypeRep -> [TypeRep]
- splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- mkFunTy :: TypeRep -> TypeRep -> TypeRep
- funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
- gcast2 :: (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b))
- gcast1 :: (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a))
- gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
- eqT :: (Typeable a, Typeable b) => Maybe (a :~: b)
- cast :: (Typeable a, Typeable b) => a -> Maybe b
- showsTypeRep :: TypeRep -> ShowS
- typeRep :: Typeable a => proxy a -> TypeRep
- typeOf :: Typeable a => a -> TypeRep
- type TypeRep = SomeTypeRep
- rnfTyCon :: TyCon -> ()
- tyConFingerprint :: TyCon -> Fingerprint
- tyConName :: TyCon -> String
- tyConModule :: TyCon -> String
- tyConPackage :: TyCon -> String
- data (a :: k) :~: (b :: k) :: forall k. k -> k -> * where
- data (a :: k1) :~~: (b :: k2) :: forall k1 k2. k1 -> k2 -> * where
- module Data.Generics.SYB.WithClass.Context
- data Fixity
- type ConIndex = Int
- data ConstrRep
- data DataRep
- data Constr = Constr {}
- data DataType = DataType {}
- newtype Qr r a = Qr {
- unQr :: r -> r
- type GenericQ ctx r = forall a. Data ctx a => a -> r
- type GenericM m ctx = forall a. Data ctx a => a -> m a
- newtype ID x = ID {
- unID :: x
- type GenericT ctx = forall a. Data ctx a => a -> a
- class (Typeable a, Sat (ctx a)) => Data ctx a where
- data Proxy (a :: * -> *)
- gmapT :: Proxy ctx -> GenericT ctx -> GenericT ctx
- gmapM :: Monad m => Proxy ctx -> GenericM m ctx -> GenericM m ctx
- gmapQ :: Proxy ctx -> GenericQ ctx r -> GenericQ ctx [r]
- gmapQr :: Data ctx a => Proxy ctx -> (r' -> r -> r) -> r -> GenericQ ctx r' -> a -> r
- fromConstr :: Data ctx a => Proxy ctx -> Constr -> a
- fromConstrB :: Data ctx a => Proxy ctx -> (forall b. Data ctx b => b) -> Constr -> a
- fromConstrM :: (Monad m, Data ctx a) => Proxy ctx -> (forall b. Data ctx b => m b) -> Constr -> m a
- dataTypeName :: DataType -> String
- dataTypeRep :: DataType -> DataRep
- constrType :: Constr -> DataType
- constrRep :: Constr -> ConstrRep
- repConstr :: DataType -> ConstrRep -> Constr
- mkDataType :: String -> [Constr] -> DataType
- mkConstr :: DataType -> String -> [String] -> Fixity -> Constr
- dataTypeConstrs :: DataType -> [Constr]
- constrFields :: Constr -> [String]
- constrFixity :: Constr -> Fixity
- showConstr :: Constr -> String
- readConstr :: DataType -> String -> Maybe Constr
- isAlgType :: DataType -> Bool
- indexConstr :: DataType -> ConIndex -> Constr
- constrIndex :: Constr -> ConIndex
- maxConstrIndex :: DataType -> ConIndex
- mkIntType :: String -> DataType
- mkFloatType :: String -> DataType
- mkStringType :: String -> DataType
- mkPrimType :: DataRep -> String -> DataType
- mkPrimCon :: DataType -> String -> ConstrRep -> Constr
- mkIntConstr :: DataType -> Integer -> Constr
- mkFloatConstr :: DataType -> Double -> Constr
- mkStringConstr :: DataType -> String -> Constr
- mkNorepType :: String -> DataType
- isNorepType :: DataType -> Bool
Documentation
The class Typeable
allows a concrete representation of a type to
be calculated.
typeRep#
Instances
Eq TyCon | |
Ord TyCon | |
Show TyCon | Since: base-2.1 |
Sat (ctx TyCon) => Data ctx TyCon Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> TyCon -> w TyCon Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon Source # toConstr :: Proxy ctx -> TyCon -> Constr Source # dataTypeOf :: Proxy ctx -> TyCon -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w TyCon) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w TyCon) Source # |
rnfTypeRep :: TypeRep -> () #
Force a TypeRep
to normal form.
typeRepFingerprint :: TypeRep -> Fingerprint #
Takes a value of type a
and returns a concrete representation
of that type.
Since: base-4.7.0.0
typeRepTyCon :: TypeRep -> TyCon #
Observe the type constructor of a quantified type representation.
typeRepArgs :: TypeRep -> [TypeRep] #
Observe the argument types of a type representation
splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) #
Splits a type constructor application. Note that if the type constructor is polymorphic, this will not return the kinds that were used.
funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep #
Applies a type to a function type. Returns: Just u
if the first argument
represents a function of type t -> u
and the second argument represents a
function of type t
. Otherwise, returns Nothing
.
gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b) #
A flexible variation parameterised in a type constructor
eqT :: (Typeable a, Typeable b) => Maybe (a :~: b) #
Extract a witness of equality of two types
Since: base-4.7.0.0
showsTypeRep :: TypeRep -> ShowS #
Show a type representation
typeRep :: Typeable a => proxy a -> TypeRep #
Takes a value of type a
and returns a concrete representation
of that type.
Since: base-4.7.0.0
type TypeRep = SomeTypeRep #
A quantified type representation.
tyConFingerprint :: TyCon -> Fingerprint #
tyConModule :: TyCon -> String #
tyConPackage :: TyCon -> String #
data (a :: k) :~: (b :: k) :: forall k. k -> k -> * where infix 4 #
Propositional equality. If a :~: b
is inhabited by some terminating
value, then the type a
is the same as the type b
. To use this equality
in practice, pattern-match on the a :~: b
to get out the Refl
constructor;
in the body of the pattern-match, the compiler knows that a ~ b
.
Since: base-4.7.0.0
Instances
TestEquality ((:~:) a :: k -> *) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
a ~ b => Enum (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
Eq (a :~: b) | |
Ord (a :~: b) | |
Defined in Data.Type.Equality | |
a ~ b => Read (a :~: b) | Since: base-4.7.0.0 |
Show (a :~: b) | |
data (a :: k1) :~~: (b :: k2) :: forall k1 k2. k1 -> k2 -> * where infix 4 #
Kind heterogeneous propositional equality. Like :~:
, a :~~: b
is
inhabited by a terminating value if and only if a
is the same type as b
.
Since: base-4.10.0.0
Instances
TestEquality ((:~~:) a :: k -> *) | Since: base-4.10.0.0 |
Defined in Data.Type.Equality | |
a ~~ b => Bounded (a :~~: b) | Since: base-4.10.0.0 |
a ~~ b => Enum (a :~~: b) | Since: base-4.10.0.0 |
Defined in Data.Type.Equality succ :: (a :~~: b) -> a :~~: b # pred :: (a :~~: b) -> a :~~: b # fromEnum :: (a :~~: b) -> Int # enumFrom :: (a :~~: b) -> [a :~~: b] # enumFromThen :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] # enumFromTo :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] # enumFromThenTo :: (a :~~: b) -> (a :~~: b) -> (a :~~: b) -> [a :~~: b] # | |
Eq (a :~~: b) | Since: base-4.10.0.0 |
Ord (a :~~: b) | Since: base-4.10.0.0 |
a ~~ b => Read (a :~~: b) | Since: base-4.10.0.0 |
Show (a :~~: b) | Since: base-4.10.0.0 |
Unique index for datatype constructors. | Textual order is respected. Starts at 1.
Representation of constructors
Representation of datatypes. | A package of constructor representations with names of type and module. | The list of constructors could be an array, a balanced tree, or others.
Instances
Show DataType Source # | |
Sat (ctx DataType) => Data ctx DataType Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> DataType -> w DataType Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataType Source # toConstr :: Proxy ctx -> DataType -> Constr Source # dataTypeOf :: Proxy ctx -> DataType -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w DataType) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w DataType) Source # |
class (Typeable a, Sat (ctx a)) => Data ctx a where Source #
gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> a -> w a Source #
gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a Source #
toConstr :: Proxy ctx -> a -> Constr Source #
dataTypeOf :: Proxy ctx -> a -> DataType Source #
dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w a) Source #
Mediate types and unary type constructors
dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w a) Source #
Mediate types and binary type constructors
Instances
Sat (ctx Handle) => Data ctx Handle Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Handle -> w Handle Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Handle Source # toConstr :: Proxy ctx -> Handle -> Constr Source # dataTypeOf :: Proxy ctx -> Handle -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Handle) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Handle) Source # | |
Sat (ctx DataType) => Data ctx DataType Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> DataType -> w DataType Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataType Source # toConstr :: Proxy ctx -> DataType -> Constr Source # dataTypeOf :: Proxy ctx -> DataType -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w DataType) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w DataType) Source # | |
Sat (ctx TyCon) => Data ctx TyCon Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> TyCon -> w TyCon Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon Source # toConstr :: Proxy ctx -> TyCon -> Constr Source # dataTypeOf :: Proxy ctx -> TyCon -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w TyCon) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w TyCon) Source # | |
Sat (ctx TypeRep) => Data ctx TypeRep Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> TypeRep -> w TypeRep Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeRep Source # toConstr :: Proxy ctx -> TypeRep -> Constr Source # dataTypeOf :: Proxy ctx -> TypeRep -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w TypeRep) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w TypeRep) Source # | |
Sat (ctx ()) => Data ctx () Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> () -> w () Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c () Source # toConstr :: Proxy ctx -> () -> Constr Source # dataTypeOf :: Proxy ctx -> () -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w ()) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w ()) Source # | |
Sat (ctx Ordering) => Data ctx Ordering Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Ordering -> w Ordering Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering Source # toConstr :: Proxy ctx -> Ordering -> Constr Source # dataTypeOf :: Proxy ctx -> Ordering -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Ordering) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Ordering) Source # | |
Sat (ctx Word64) => Data ctx Word64 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Word64 -> w Word64 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 Source # toConstr :: Proxy ctx -> Word64 -> Constr Source # dataTypeOf :: Proxy ctx -> Word64 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Word64) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Word64) Source # | |
Sat (ctx Word32) => Data ctx Word32 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Word32 -> w Word32 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 Source # toConstr :: Proxy ctx -> Word32 -> Constr Source # dataTypeOf :: Proxy ctx -> Word32 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Word32) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Word32) Source # | |
Sat (ctx Word16) => Data ctx Word16 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Word16 -> w Word16 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word16 Source # toConstr :: Proxy ctx -> Word16 -> Constr Source # dataTypeOf :: Proxy ctx -> Word16 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Word16) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Word16) Source # | |
Sat (ctx Word8) => Data ctx Word8 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Word8 -> w Word8 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 Source # toConstr :: Proxy ctx -> Word8 -> Constr Source # dataTypeOf :: Proxy ctx -> Word8 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Word8) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Word8) Source # | |
Sat (ctx Word) => Data ctx Word Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Word -> w Word Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word Source # toConstr :: Proxy ctx -> Word -> Constr Source # dataTypeOf :: Proxy ctx -> Word -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Word) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Word) Source # | |
Sat (ctx Int64) => Data ctx Int64 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Int64 -> w Int64 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 Source # toConstr :: Proxy ctx -> Int64 -> Constr Source # dataTypeOf :: Proxy ctx -> Int64 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Int64) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Int64) Source # | |
Sat (ctx Int32) => Data ctx Int32 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Int32 -> w Int32 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 Source # toConstr :: Proxy ctx -> Int32 -> Constr Source # dataTypeOf :: Proxy ctx -> Int32 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Int32) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Int32) Source # | |
Sat (ctx Int16) => Data ctx Int16 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Int16 -> w Int16 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int16 Source # toConstr :: Proxy ctx -> Int16 -> Constr Source # dataTypeOf :: Proxy ctx -> Int16 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Int16) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Int16) Source # | |
Sat (ctx Int8) => Data ctx Int8 Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Int8 -> w Int8 Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int8 Source # toConstr :: Proxy ctx -> Int8 -> Constr Source # dataTypeOf :: Proxy ctx -> Int8 -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Int8) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Int8) Source # | |
Sat (ctx Integer) => Data ctx Integer Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Integer -> w Integer Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer Source # toConstr :: Proxy ctx -> Integer -> Constr Source # dataTypeOf :: Proxy ctx -> Integer -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Integer) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Integer) Source # | |
Sat (ctx Int) => Data ctx Int Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Int -> w Int Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int Source # toConstr :: Proxy ctx -> Int -> Constr Source # dataTypeOf :: Proxy ctx -> Int -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Int) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Int) Source # | |
Sat (ctx Double) => Data ctx Double Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Double -> w Double Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source # toConstr :: Proxy ctx -> Double -> Constr Source # dataTypeOf :: Proxy ctx -> Double -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Double) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Double) Source # | |
Sat (ctx Float) => Data ctx Float Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Float -> w Float Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source # toConstr :: Proxy ctx -> Float -> Constr Source # dataTypeOf :: Proxy ctx -> Float -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Float) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Float) Source # | |
Sat (ctx Char) => Data ctx Char Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Char -> w Char Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char Source # toConstr :: Proxy ctx -> Char -> Constr Source # dataTypeOf :: Proxy ctx -> Char -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Char) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Char) Source # | |
Sat (ctx Bool) => Data ctx Bool Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Bool -> w Bool Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool Source # toConstr :: Proxy ctx -> Bool -> Constr Source # dataTypeOf :: Proxy ctx -> Bool -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w Bool) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w Bool) Source # | |
(Data ctx (ForeignPtr Word8), Data ctx Int, Sat (ctx ByteString), Sat (ctx (ForeignPtr Word8)), Sat (ctx Int)) => Data ctx ByteString Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> ByteString -> w ByteString Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString Source # toConstr :: Proxy ctx -> ByteString -> Constr Source # dataTypeOf :: Proxy ctx -> ByteString -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w ByteString) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w ByteString) Source # | |
(Data ctx ByteString, Sat (ctx ByteString), Sat (ctx ByteString)) => Data ctx ByteString Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> ByteString -> w ByteString Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString Source # toConstr :: Proxy ctx -> ByteString -> Constr Source # dataTypeOf :: Proxy ctx -> ByteString -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w ByteString) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w ByteString) Source # | |
(Sat (ctx (Set a)), Data ctx a, Ord a) => Data ctx (Set a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Set a -> w (Set a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) Source # toConstr :: Proxy ctx -> Set a -> Constr Source # dataTypeOf :: Proxy ctx -> Set a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Set a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (Set a)) Source # | |
(Sat (ctx (MVar a)), Typeable a) => Data ctx (MVar a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> MVar a -> w (MVar a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MVar a) Source # toConstr :: Proxy ctx -> MVar a -> Constr Source # dataTypeOf :: Proxy ctx -> MVar a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (MVar a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (MVar a)) Source # | |
(Sat (ctx (ForeignPtr a)), Typeable a) => Data ctx (ForeignPtr a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> ForeignPtr a -> w (ForeignPtr a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignPtr a) Source # toConstr :: Proxy ctx -> ForeignPtr a -> Constr Source # dataTypeOf :: Proxy ctx -> ForeignPtr a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (ForeignPtr a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (ForeignPtr a)) Source # | |
(Sat (ctx (IORef a)), Typeable a) => Data ctx (IORef a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> IORef a -> w (IORef a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IORef a) Source # toConstr :: Proxy ctx -> IORef a -> Constr Source # dataTypeOf :: Proxy ctx -> IORef a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (IORef a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (IORef a)) Source # | |
(Sat (ctx (StablePtr a)), Typeable a) => Data ctx (StablePtr a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> StablePtr a -> w (StablePtr a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StablePtr a) Source # toConstr :: Proxy ctx -> StablePtr a -> Constr Source # dataTypeOf :: Proxy ctx -> StablePtr a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (StablePtr a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (StablePtr a)) Source # | |
(Sat (ctx (Ptr a)), Typeable a) => Data ctx (Ptr a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Ptr a -> w (Ptr a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source # toConstr :: Proxy ctx -> Ptr a -> Constr Source # dataTypeOf :: Proxy ctx -> Ptr a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Ptr a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (Ptr a)) Source # | |
(Sat (ctx (IO a)), Typeable a) => Data ctx (IO a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> IO a -> w (IO a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IO a) Source # toConstr :: Proxy ctx -> IO a -> Constr Source # dataTypeOf :: Proxy ctx -> IO a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (IO a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (IO a)) Source # | |
(Sat (ctx (Maybe a)), Data ctx a) => Data ctx (Maybe a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Maybe a -> w (Maybe a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) Source # toConstr :: Proxy ctx -> Maybe a -> Constr Source # dataTypeOf :: Proxy ctx -> Maybe a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Maybe a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (Maybe a)) Source # | |
(Sat (ctx [a]), Data ctx a) => Data ctx [a] Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> [a] -> w [a] Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c [a] Source # toConstr :: Proxy ctx -> [a] -> Constr Source # dataTypeOf :: Proxy ctx -> [a] -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w [a]) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w [a]) Source # | |
(Sat (ctx (Ratio a)), Data ctx a, Integral a) => Data ctx (Ratio a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Ratio a -> w (Ratio a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ratio a) Source # toConstr :: Proxy ctx -> Ratio a -> Constr Source # dataTypeOf :: Proxy ctx -> Ratio a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Ratio a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (Ratio a)) Source # | |
(Sat (ctx (Map a b)), Data ctx a, Data ctx b, Ord a) => Data ctx (Map a b) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c. Data ctx b0 => w (b0 -> c) -> b0 -> w c) -> (forall g. g -> w g) -> Map a b -> w (Map a b) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map a b) Source # toConstr :: Proxy ctx -> Map a b -> Constr Source # dataTypeOf :: Proxy ctx -> Map a b -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (Map a b)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c. (Data ctx b0, Data ctx c) => w (t b0 c)) -> Maybe (w (Map a b)) Source # | |
(Sat (ctx [b]), Sat (ctx (Array a b)), Typeable a, Data ctx b, Data ctx [b], Ix a) => Data ctx (Array a b) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c. Data ctx b0 => w (b0 -> c) -> b0 -> w c) -> (forall g. g -> w g) -> Array a b -> w (Array a b) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a b) Source # toConstr :: Proxy ctx -> Array a b -> Constr Source # dataTypeOf :: Proxy ctx -> Array a b -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (Array a b)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c. (Data ctx b0, Data ctx c) => w (t b0 c)) -> Maybe (w (Array a b)) Source # | |
(Sat (ctx (ST s a)), Typeable s, Typeable a) => Data ctx (ST s a) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> ST s a -> w (ST s a) Source # gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ST s a) Source # toConstr :: Proxy ctx -> ST s a -> Constr Source # dataTypeOf :: Proxy ctx -> ST s a -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (ST s a)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (ST s a)) Source # | |
(Sat (ctx (a, b)), Data ctx a, Data ctx b) => Data ctx (a, b) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c. Data ctx b0 => w (b0 -> c) -> b0 -> w c) -> (forall g. g -> w g) -> (a, b) -> w (a, b) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a, b) Source # toConstr :: Proxy ctx -> (a, b) -> Constr Source # dataTypeOf :: Proxy ctx -> (a, b) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a, b)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c. (Data ctx b0, Data ctx c) => w (t b0 c)) -> Maybe (w (a, b)) Source # | |
(Sat (ctx (a -> b)), Data ctx a, Data ctx b) => Data ctx (a -> b) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c. Data ctx b0 => w (b0 -> c) -> b0 -> w c) -> (forall g. g -> w g) -> (a -> b) -> w (a -> b) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a -> b) Source # toConstr :: Proxy ctx -> (a -> b) -> Constr Source # dataTypeOf :: Proxy ctx -> (a -> b) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a -> b)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c. (Data ctx b0, Data ctx c) => w (t b0 c)) -> Maybe (w (a -> b)) Source # | |
(Sat (ctx (Either a b)), Data ctx a, Data ctx b) => Data ctx (Either a b) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c. Data ctx b0 => w (b0 -> c) -> b0 -> w c) -> (forall g. g -> w g) -> Either a b -> w (Either a b) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) Source # toConstr :: Proxy ctx -> Either a b -> Constr Source # dataTypeOf :: Proxy ctx -> Either a b -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (Either a b)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c. (Data ctx b0, Data ctx c) => w (t b0 c)) -> Maybe (w (Either a b)) Source # | |
(Sat (ctx (a, b, c)), Data ctx a, Data ctx b, Data ctx c) => Data ctx (a, b, c) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c0. Data ctx b0 => w (b0 -> c0) -> b0 -> w c0) -> (forall g. g -> w g) -> (a, b, c) -> w (a, b, c) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c) Source # toConstr :: Proxy ctx -> (a, b, c) -> Constr Source # dataTypeOf :: Proxy ctx -> (a, b, c) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a, b, c)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c0. (Data ctx b0, Data ctx c0) => w (t b0 c0)) -> Maybe (w (a, b, c)) Source # | |
(Sat (ctx (a, b, c, d)), Data ctx a, Data ctx b, Data ctx c, Data ctx d) => Data ctx (a, b, c, d) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c0. Data ctx b0 => w (b0 -> c0) -> b0 -> w c0) -> (forall g. g -> w g) -> (a, b, c, d) -> w (a, b, c, d) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d) Source # toConstr :: Proxy ctx -> (a, b, c, d) -> Constr Source # dataTypeOf :: Proxy ctx -> (a, b, c, d) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a, b, c, d)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c0. (Data ctx b0, Data ctx c0) => w (t b0 c0)) -> Maybe (w (a, b, c, d)) Source # | |
(Sat (ctx (a, b, c, d, e)), Data ctx a, Data ctx b, Data ctx c, Data ctx d, Data ctx e) => Data ctx (a, b, c, d, e) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c0. Data ctx b0 => w (b0 -> c0) -> b0 -> w c0) -> (forall g. g -> w g) -> (a, b, c, d, e) -> w (a, b, c, d, e) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e) Source # toConstr :: Proxy ctx -> (a, b, c, d, e) -> Constr Source # dataTypeOf :: Proxy ctx -> (a, b, c, d, e) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a, b, c, d, e)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c0. (Data ctx b0, Data ctx c0) => w (t b0 c0)) -> Maybe (w (a, b, c, d, e)) Source # | |
(Sat (ctx (a, b, c, d, e, f)), Data ctx a, Data ctx b, Data ctx c, Data ctx d, Data ctx e, Data ctx f) => Data ctx (a, b, c, d, e, f) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c0. Data ctx b0 => w (b0 -> c0) -> b0 -> w c0) -> (forall g. g -> w g) -> (a, b, c, d, e, f) -> w (a, b, c, d, e, f) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e, f) Source # toConstr :: Proxy ctx -> (a, b, c, d, e, f) -> Constr Source # dataTypeOf :: Proxy ctx -> (a, b, c, d, e, f) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a, b, c, d, e, f)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c0. (Data ctx b0, Data ctx c0) => w (t b0 c0)) -> Maybe (w (a, b, c, d, e, f)) Source # | |
(Sat (ctx (a, b, c, d, e, f, g)), Data ctx a, Data ctx b, Data ctx c, Data ctx d, Data ctx e, Data ctx f, Data ctx g) => Data ctx (a, b, c, d, e, f, g) Source # | |
Defined in Data.Generics.SYB.WithClass.Instances gfoldl :: Proxy ctx -> (forall b0 c0. Data ctx b0 => w (b0 -> c0) -> b0 -> w c0) -> (forall g0. g0 -> w g0) -> (a, b, c, d, e, f, g) -> w (a, b, c, d, e, f, g) Source # gunfold :: Proxy ctx -> (forall b0 r. Data ctx b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e, f, g) Source # toConstr :: Proxy ctx -> (a, b, c, d, e, f, g) -> Constr Source # dataTypeOf :: Proxy ctx -> (a, b, c, d, e, f, g) -> DataType Source # dataCast1 :: Typeable t => Proxy ctx -> (forall b0. Data ctx b0 => w (t b0)) -> Maybe (w (a, b, c, d, e, f, g)) Source # dataCast2 :: Typeable t => Proxy ctx -> (forall b0 c0. (Data ctx b0, Data ctx c0) => w (t b0 c0)) -> Maybe (w (a, b, c, d, e, f, g)) Source # |
fromConstrB :: Data ctx a => Proxy ctx -> (forall b. Data ctx b => b) -> Constr -> a Source #
Build a term and use a generic function for subterms
fromConstrM :: (Monad m, Data ctx a) => Proxy ctx -> (forall b. Data ctx b => m b) -> Constr -> m a Source #
Monadic variation on "fromConstrB"
dataTypeName :: DataType -> String Source #
Gets the type constructor including the module
dataTypeRep :: DataType -> DataRep Source #
Gets the public presentation of datatypes
constrType :: Constr -> DataType Source #
Gets the datatype of a constructor
dataTypeConstrs :: DataType -> [Constr] Source #
Gets the constructors
constrFields :: Constr -> [String] Source #
Gets the field labels of a constructor
constrFixity :: Constr -> Fixity Source #
Gets the fixity of a constructor
showConstr :: Constr -> String Source #
Gets the string for a constructor
constrIndex :: Constr -> ConIndex Source #
Gets the index of a constructor
maxConstrIndex :: DataType -> ConIndex Source #
Gets the maximum constructor index
mkFloatType :: String -> DataType Source #
Constructs the Float type
mkStringType :: String -> DataType Source #
Constructs the String type
mkNorepType :: String -> DataType Source #
Constructs a non-representation
isNorepType :: DataType -> Bool Source #
Test for a non-representable type