uniplate-1.6.13: Help writing simple, concise and fast generic operations.
Safe HaskellNone
LanguageHaskell2010

Data.Generics.Uniplate.Typeable

Description

RECOMMENDATION: Use Data.Generics.Uniplate.Data instead - it usually performs faster (sometimes significantly so) and requires no special instance declarations.

This module supplies a method for writing Uniplate / Biplate instances. One instance declaration is required for each data type you wish to work with. The instances can be generated using Derive: http://community.haskell.org/~ndm/derive/.

To take an example:

data Expr = Var Int | Neg Expr | Add Expr Expr
            deriving Typeable

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
Synopsis

Documentation

The Class

class PlateAll from to where Source #

This class should be defined for each data type of interest.

Methods

plateAll :: from -> Type from to Source #

This method should be defined using plate and |+, |-.

Instances

Instances details
PlateAll Bool to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Bool -> Type Bool to Source #

PlateAll Char to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Char -> Type Char to Source #

PlateAll Double to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Double -> Type Double to Source #

PlateAll Float to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Float -> Type Float to Source #

PlateAll Int to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Int -> Type Int to Source #

PlateAll Integer to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Integer -> Type Integer to Source #

PlateAll () to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: () -> Type () to Source #

(PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll [from] to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: [from] -> Type [from] to Source #

(PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll (Maybe from) to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Maybe from -> Type (Maybe from) to Source #

(Integral a, PlateAll a to, Typeable a, Typeable to, Uniplate to) => PlateAll (Ratio a) to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Ratio a -> Type (Ratio a) to Source #

(PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (Either a b) to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: Either a b -> Type (Either a b) to Source #

(PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (a, b) to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: (a, b) -> Type (a, b) to Source #

(PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, Typeable to, Uniplate to) => PlateAll (a, b, c) to Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: (a, b, c) -> Type (a, b, c) to Source #

(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 Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: (a, b, c, d) -> Type (a, b, c, d) to Source #

(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 Source # 
Instance details

Defined in Data.Generics.Uniplate.Typeable

Methods

plateAll :: (a, b, c, d, e) -> Type (a, b, c, d, e) to Source #

The Combinators

plate :: from -> Type from to Source #

The main combinator used to start the chain.

(|+) :: (Typeable item, Typeable to, PlateAll item to) => Type (item -> from) to -> item -> Type from to Source #

The field to the right may contain the target.

(|-) :: Type (item -> from) to -> item -> Type from to Source #

The field to the right does not contain the target. This can be used as either an optimisation, or more commonly for excluding primitives such as Int.

plateProject :: (Typeable item, Typeable to, PlateAll item to) => (from -> item) -> (item -> from) -> from -> Type from to Source #

Write an instance in terms of a projection/injection pair. Usually used to define instances for abstract containers such as Map:

instance (Ord a, Typeable a, PlateAll a c, Typeable b, PlateAll b c,
         Typeable c, PlateAll c c) => PlateAll (Map.Map a b) c where
    plateAll = plateProject Map.toList Map.fromList

Orphan instances

PlateAll a a => Uniplate a Source # 
Instance details

Methods

uniplate :: a -> (Str a, Str a -> a) Source #

descend :: (a -> a) -> a -> a Source #

descendM :: Applicative m => (a -> m a) -> a -> m a Source #

(Typeable a, Typeable b, Uniplate b, PlateAll a b) => Biplate a b Source # 
Instance details

Methods

biplate :: a -> (Str b, Str b -> a) Source #

descendBi :: (b -> b) -> a -> a Source #

descendBiM :: Applicative m => (b -> m b) -> a -> m a Source #