Safe Haskell | None |
---|
Deprecated: Use Data.Generics.Uniplate.Typeable instead
DEPRECATED: Use Data.Generics.Uniplate.Typeable instead.
This module supplies a method for writing Biplate
instances more easily.
To take an example:
data Expr = Var Int | Neg Expr | Add Expr Expr instance Typeable Expr where ... instance (Typeable a, Uniplate a) => PlateAll Expr a where plateAll (Var x ) = plate Var |- x plateAll (Neg x ) = plate Neg |+ x plateAll (Add x y) = plate Add |+ x |+ y instance Uniplate Expr where uniplate = uniplateAll
- module Data.Generics.Biplate
- module Data.Typeable
- class PlateAll from to where
- plateAll :: from -> Type from to
- uniplateAll :: PlateAll a b => a -> (Str b, Str b -> a)
- plate :: from -> Type from to
- (|+) :: (Typeable item, Typeable to, PlateAll item to) => Type (item -> from) to -> item -> Type from to
- (|-) :: Type (item -> from) to -> item -> Type from to
Documentation
module Data.Generics.Biplate
module Data.Typeable
The Class
class PlateAll from to whereSource
This class represents going from the container type to the target.
PlateAll Bool to | |
PlateAll Char to | |
PlateAll Double to | |
PlateAll Float to | |
PlateAll Int to | |
PlateAll Integer to | |
PlateAll () to | |
(PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll [from] to | |
(PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll (Maybe from) to | |
(PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (Either a b) to | |
(PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (a, b) to | |
(PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, Typeable to, Uniplate to) => PlateAll (a, b, c) to | |
(PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, PlateAll d to, Typeable d, Typeable to, Uniplate to) => PlateAll (a, b, c, d) to | |
(PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, PlateAll d to, Typeable d, PlateAll e to, Typeable e, Typeable to, Uniplate to) => PlateAll (a, b, c, d, e) to |
uniplateAll :: PlateAll a b => a -> (Str b, Str b -> a)Source
The Combinators
plate :: from -> Type from toSource
The main combinator used to start the chain.
The following rule can be used for optimisation:
plate Ctor |- x == plate (Ctor x)