syb-with-class-0.6.1.6: Scrap Your Boilerplate With Class

Safe HaskellNone
LanguageHaskell98

Data.Generics.SYB.WithClass.Basics

Synopsis

Documentation

data Proxy a Source

class (Typeable a, Sat (ctx a)) => Data ctx a where Source

Minimal complete definition

toConstr

Methods

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 :: 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 Handle) => Data ctx Handle 
Sat (ctx DataType) => Data ctx DataType 
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 
(Data ctx (ForeignPtr Word8), Data ctx Int, Sat (ctx ByteString), Sat (ctx (ForeignPtr Word8)), Sat (ctx Int)) => Data ctx ByteString 
(Data ctx ByteString, Sat (ctx ByteString), Sat (ctx ByteString)) => Data ctx ByteString 
(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 (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 (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)), 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 (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) 

type GenericT ctx = forall a. Data ctx a => a -> a Source

gmapT :: Proxy ctx -> GenericT ctx -> GenericT ctx Source

newtype ID x Source

Constructors

ID 

Fields

unID :: x
 

type GenericM m ctx = forall a. Data ctx a => a -> m a Source

gmapM :: Monad m => Proxy ctx -> GenericM m ctx -> GenericM m ctx Source

type GenericQ ctx r = forall a. Data ctx a => a -> r Source

gmapQ :: Proxy ctx -> GenericQ ctx r -> GenericQ ctx [r] Source

gmapQr :: Data ctx a => Proxy ctx -> (r' -> r -> r) -> r -> GenericQ ctx r' -> a -> r Source

newtype Qr r a Source

Constructors

Qr 

Fields

unQr :: r -> r
 

fromConstr :: Data ctx a => Proxy ctx -> Constr -> a Source

Build a term skeleton

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"

data DataType Source

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.

Constructors

DataType 

Fields

tycon :: String
 
datarep :: DataRep
 

Instances

data Constr Source

Representation of constructors

Instances

Eq Constr

Equality of constructors

Show Constr 

data DataRep Source

Public representation of datatypes

Instances

data ConstrRep Source

Public representation of constructors

type ConIndex = Int Source

Unique index for datatype constructors. | Textual order is respected. Starts at 1.

data Fixity Source

Fixity of constructors

Constructors

Prefix 
Infix 

Instances

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

constrRep :: Constr -> ConstrRep Source

Gets the public presentation of constructors

repConstr :: DataType -> ConstrRep -> Constr Source

Look up a constructor by its representation

mkDataType :: String -> [Constr] -> DataType Source

Constructs an algebraic datatype

mkConstr :: DataType -> String -> [String] -> Fixity -> Constr Source

Constructs 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

readConstr :: DataType -> String -> Maybe Constr Source

Lookup a constructor via a string

isAlgType :: DataType -> Bool Source

Test for an algebraic type

indexConstr :: DataType -> ConIndex -> Constr Source

Gets the constructor for an index

constrIndex :: Constr -> ConIndex Source

Gets the index of a constructor

maxConstrIndex :: DataType -> ConIndex Source

Gets the maximum constructor index

mkIntType :: String -> DataType Source

Constructs the Int type

mkFloatType :: String -> DataType Source

Constructs the Float type

mkStringType :: String -> DataType Source

Constructs the String type

mkPrimType :: DataRep -> String -> DataType Source

Helper for mkIntType, mkFloatType, mkStringType

mkNorepType :: String -> DataType Source

Constructs a non-representation

isNorepType :: DataType -> Bool Source

Test for a non-representable type