| Safe Haskell | None |
|---|
Data.Generics.Geniplate
- genUniverseBi :: Name -> Q Exp
- genUniverseBiT :: [TypeQ] -> Name -> Q Exp
- genTransformBi :: Name -> Q Exp
- genTransformBiT :: [TypeQ] -> Name -> Q Exp
- genTransformBiM :: Name -> Q Exp
- genTransformBiMT :: [TypeQ] -> Name -> Q Exp
- class UniverseBi s t where
- universeBi :: s -> [t]
- universe :: UniverseBi a a => a -> [a]
- instanceUniverseBi :: TypeQ -> Q [Dec]
- instanceUniverseBiT :: [TypeQ] -> TypeQ -> Q [Dec]
- class TransformBi s t where
- transformBi :: (s -> s) -> t -> t
- transform :: TransformBi a a => (a -> a) -> a -> a
- instanceTransformBi :: TypeQ -> Q [Dec]
- instanceTransformBiT :: [TypeQ] -> TypeQ -> Q [Dec]
- class TransformBiM m s t where
- transformBiM :: (s -> m s) -> t -> m t
- transformM :: TransformBiM m a a => (a -> m a) -> a -> m a
- instanceTransformBiM :: TypeQ -> TypeQ -> Q [Dec]
- instanceTransformBiMT :: [TypeQ] -> TypeQ -> TypeQ -> Q [Dec]
Documentation
Generate TH code for a function that extracts all subparts of a certain type.
The argument to genUniverseBi is a name with the type S -> [T], for some types
S and T. The function will extract all subparts of type T from S.
Arguments
| :: [TypeQ] | types not touched by |
| -> Name | function of type |
| -> Q Exp |
Same as genUniverseBi, but does not look inside any types mention in the
list of types.
Generate TH code for a function that transforms all subparts of a certain type.
The argument to genTransformBi is a name with the type (S->S) -> T -> T, for some types
S and T. The function will transform all subparts of type S inside T using the given function.
genTransformBiT :: [TypeQ] -> Name -> Q ExpSource
Same as genTransformBi, but does not look inside any types mention in the
list of types.
genTransformBiM :: Name -> Q ExpSource
universe :: UniverseBi a a => a -> [a]Source
Create a UniverseBi instance.
The TypeQ argument should be a pair; the source and target types for universeBi.
Arguments
| :: [TypeQ] | types not touched by |
| -> TypeQ | (source, target) types |
| -> Q [Dec] |
Create a UniverseBi instance with certain types being abstract.
The TypeQ argument should be a pair; the source and target types for universeBi.
class TransformBi s t whereSource
Class for transformBi.
Methods
transformBi :: (s -> s) -> t -> tSource
transform :: TransformBi a a => (a -> a) -> a -> aSource
Create a TransformBi instance.
The TypeQ argument should be a pair; the inner and outer types for transformBi.
Arguments
| :: [TypeQ] | types not touched by |
| -> TypeQ | (inner, outer) types |
| -> Q [Dec] |
Create a TransformBi instance with certain types being abstract.
The TypeQ argument should be a pair; the inner and outer types for transformBi.
class TransformBiM m s t whereSource
Class for transformBiM.
Methods
transformBiM :: (s -> m s) -> t -> m tSource
transformM :: TransformBiM m a a => (a -> m a) -> a -> m aSource
instanceTransformBiM :: TypeQ -> TypeQ -> Q [Dec]Source
Create a TransformBiM instance.
instanceTransformBiMT :: [TypeQ] -> TypeQ -> TypeQ -> Q [Dec]Source
Create a TransformBiM instance with certain types being abstract.