Data.Generics.SYB.WithClass.Basics
- module Data.Typeable
- module Data.Generics.SYB.WithClass.Context
- data Proxy a
- class (Typeable a, Sat (ctx a)) => Data ctx a  where- gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> a -> w a
- gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a
- toConstr :: Proxy ctx -> a -> Constr
- dataTypeOf :: Proxy ctx -> a -> DataType
- dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w a)
- dataCast2 :: Typeable2 t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w a)
 
- type GenericT ctx = forall a. Data ctx a => a -> a
- gmapT :: Proxy ctx -> GenericT ctx -> GenericT ctx
- newtype  ID x = ID {- unID :: x
 
- type GenericM m ctx = forall a. Data ctx a => a -> m a
- gmapM :: Monad m => Proxy ctx -> GenericM m ctx -> GenericM m ctx
- type GenericQ ctx r = forall a. Data ctx a => a -> r
- gmapQ :: Proxy ctx -> GenericQ ctx r -> GenericQ ctx [r]
- gmapQr :: Data ctx a => Proxy ctx -> (r' -> r -> r) -> r -> GenericQ ctx r' -> a -> r
- newtype  Qr r a = Qr {- unQr :: r -> 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
- data DataType = DataType {}
- data Constr = Constr {}
- data DataRep
- data ConstrRep
- type ConIndex = Int
- data Fixity
- 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
module Data.Typeable
class (Typeable a, Sat (ctx a)) => Data ctx a whereSource
Methods
gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> a -> w aSource
gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c aSource
toConstr :: Proxy ctx -> a -> ConstrSource
dataTypeOf :: Proxy ctx -> a -> DataTypeSource
dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w a)Source
Mediate types and unary type constructors
dataCast2 :: Typeable2 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 TyCon) => Data ctx TyCon | |
| Sat (ctx TypeRep) => Data ctx TypeRep | |
| Sat (ctx ()) => Data ctx () | |
| Sat (ctx Ordering) => Data ctx Ordering | |
| Sat (ctx Word64) => Data ctx Word64 | |
| Sat (ctx Word32) => Data ctx Word32 | |
| Sat (ctx Word16) => Data ctx Word16 | |
| Sat (ctx Word8) => Data ctx Word8 | |
| Sat (ctx Word) => Data ctx Word | |
| Sat (ctx Int64) => Data ctx Int64 | |
| Sat (ctx Int32) => Data ctx Int32 | |
| Sat (ctx Int16) => Data ctx Int16 | |
| Sat (ctx Int8) => Data ctx Int8 | |
| Sat (ctx Integer) => Data ctx Integer | |
| Sat (ctx Int) => Data ctx Int | |
| Sat (ctx Double) => Data ctx Double | |
| Sat (ctx Float) => Data ctx Float | |
| Sat (ctx Char) => Data ctx Char | |
| Sat (ctx Bool) => Data ctx Bool | |
| Sat (ctx Handle) => Data ctx Handle | |
| Sat (ctx DataType) => Data ctx DataType | |
| (Data ctx (ForeignPtr Word8), Data ctx Int, Sat (ctx ByteString), Sat (ctx (ForeignPtr Word8)), Sat (ctx Int)) => Data ctx ByteString | |
| (Data ctx ByteString, Data ctx ByteString, Sat (ctx ByteString), Sat (ctx ByteString)) => Data ctx ByteString | |
| (Sat (ctx (Maybe a)), Data ctx a) => Data ctx (Maybe a) | |
| (Sat (ctx [a]), Data ctx a) => Data ctx [a] | |
| (Sat (ctx (Ratio a)), Data ctx a, Integral a) => Data ctx (Ratio a) | |
| (Sat (ctx (Set a)), Data ctx a, Ord a) => Data ctx (Set a) | |
| (Sat (ctx (MVar a)), Typeable a) => Data ctx (MVar a) | |
| (Sat (ctx (ForeignPtr a)), Typeable a) => Data ctx (ForeignPtr a) | |
| (Sat (ctx (IORef a)), Typeable a) => Data ctx (IORef a) | |
| (Sat (ctx (StablePtr a)), Typeable a) => Data ctx (StablePtr a) | |
| (Sat (ctx (Ptr a)), Typeable a) => Data ctx (Ptr a) | |
| (Sat (ctx (IO a)), Typeable a) => Data ctx (IO a) | |
| (Sat (ctx (a, b)), Data ctx a, Data ctx b) => Data ctx (a, b) | |
| (Sat (ctx (a -> b)), Data ctx a, Data ctx b) => Data ctx (a -> b) | |
| (Sat (ctx (Either a b)), Data ctx a, Data ctx b) => Data ctx (Either a b) | |
| (Sat (ctx (Map a b)), Data ctx a, Data ctx b, Ord a) => Data ctx (Map a b) | |
| (Sat (ctx [b]), Sat (ctx (Array a b)), Typeable a, Data ctx b, Data ctx [b], Ix a) => Data ctx (Array a b) | |
| (Sat (ctx (ST s a)), Typeable s, Typeable a) => Data ctx (ST s a) | |
| (Sat (ctx (a, b, c)), Data ctx a, Data ctx b, Data ctx c) => Data ctx (a, b, c) | |
| (Sat (ctx (a, b, c, d)), Data ctx a, Data ctx b, Data ctx c, Data ctx d) => Data ctx (a, b, c, d) | |
| (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) | |
| (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) | |
| (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) | 
fromConstr :: Data ctx a => Proxy ctx -> Constr -> aSource
Build a term skeleton
fromConstrB :: Data ctx a => Proxy ctx -> (forall b. Data ctx b => b) -> Constr -> aSource
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 aSource
Monadic variation on "fromConstrB"
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.
Representation of constructors
Constructors
| Constr | |
Public representation of datatypes
Public representation of constructors
Constructors
| AlgConstr ConIndex | |
| IntConstr Integer | |
| FloatConstr Double | |
| StringConstr String | 
Unique index for datatype constructors. | Textual order is respected. Starts at 1.
dataTypeName :: DataType -> StringSource
Gets the type constructor including the module
dataTypeRep :: DataType -> DataRepSource
Gets the public presentation of datatypes
constrType :: Constr -> DataTypeSource
Gets the datatype of a constructor
mkDataType :: String -> [Constr] -> DataTypeSource
Constructs an algebraic datatype
dataTypeConstrs :: DataType -> [Constr]Source
Gets the constructors
constrFields :: Constr -> [String]Source
Gets the field labels of a constructor
constrFixity :: Constr -> FixitySource
Gets the fixity of a constructor
showConstr :: Constr -> StringSource
Gets the string for a constructor
indexConstr :: DataType -> ConIndex -> ConstrSource
Gets the constructor for an index
constrIndex :: Constr -> ConIndexSource
Gets the index of a constructor
maxConstrIndex :: DataType -> ConIndexSource
Gets the maximum constructor index
mkFloatType :: String -> DataTypeSource
Constructs the Float type
mkStringType :: String -> DataTypeSource
Constructs the String type
mkPrimType :: DataRep -> String -> DataTypeSource
Helper for mkIntType, mkFloatType, mkStringType
mkIntConstr :: DataType -> Integer -> ConstrSource
mkFloatConstr :: DataType -> Double -> ConstrSource
mkStringConstr :: DataType -> String -> ConstrSource
mkNorepType :: String -> DataTypeSource
Constructs a non-representation
isNorepType :: DataType -> BoolSource
Test for a non-representable type