uniplate-1.4: Help writing simple, consise and fast generic operations.

Data.Generics.Uniplate.DataOnly

Contents

Description

This module functions identically to Data.Generics.Uniplate.Data, but instead of using the standard Uniplate / Biplate classes defined in Data.Generics.Uniplate.Operations it uses a local copy.

Only use this module if you are using both Data and Direct instances in the same project and they are conflicting.

Synopsis

The Classes

class Uniplate on whereSource

The standard Uniplate class, all operations require this.

Methods

uniplate :: on -> (Str on, Str on -> on)Source

The underlying method in the class. Taking a value, the function should return all the immediate children of the same type, and a function to replace them.

Given uniplate x = (cs, gen)

cs should be a Str on, constructed of Zero, One and Two, containing all x's direct children of the same type as x. gen should take a Str on with exactly the same structure as cs, and generate a new element with the children replaced.

Example instance:

 instance Uniplate Expr where
     uniplate (Val i  ) = (Zero               , \Zero                  -> Val i  )
     uniplate (Neg a  ) = (One a              , \(One a)               -> Neg a  )
     uniplate (Add a b) = (Two (One a) (One b), \(Two (One a) (One b)) -> Add a b)

descend :: (on -> on) -> on -> onSource

Perform a transformation on all the immediate children, then combine them back. This operation allows additional information to be passed downwards, and can be used to provide a top-down transformation.

descendM :: Monad m => (on -> m on) -> on -> m onSource

Monadic variant of descend

Instances

Data a => Uniplate a 

class Uniplate to => Biplate from to whereSource

Children are defined as the top-most items of type to starting at the root.

Methods

biplate :: from -> (Str to, Str to -> from)Source

Return all the top most children of type to within from.

If from == to then this function should return the root as the single child.

descendBi :: (to -> to) -> from -> fromSource

descendBiM :: Monad m => (to -> m to) -> from -> m fromSource

Instances

(Data a, Data b, Uniplate b) => Biplate a b 

Single Type Operations

Queries

universe :: Uniplate on => on -> [on]Source

Get all the children of a node, including itself and all children.

 universe (Add (Val 1) (Neg (Val 2))) =
     [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]

This method is often combined with a list comprehension, for example:

 vals x = [i | Val i <- universe x]

children :: Uniplate on => on -> [on]Source

Get the direct children of a node. Usually using universe is more appropriate.

Transformations

transform :: Uniplate on => (on -> on) -> on -> onSource

Transform every element in the tree, in a bottom-up manner.

For example, replacing negative literals with literals:

 negLits = transform f
    where f (Neg (Lit i)) = Lit (negate i)
          f x = x

transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m onSource

Monadic variant of transform

rewrite :: Uniplate on => (on -> Maybe on) -> on -> onSource

Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result:

 propRewrite r x = all (isNothing . r) (universe (rewrite r x))

Usually transform is more appropriate, but rewrite can give better compositionality. Given two single transformations f and g, you can construct f mplus g which performs both rewrites until a fixed point.

rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m onSource

Monadic variant of rewrite

Others

contexts :: Uniplate on => on -> [(on, on -> on)]Source

Return all the contexts and holes.

 propUniverse x = universe x == map fst (contexts x)
 propId x = all (== x) [b a | (a,b) <- contexts x]

holes :: Uniplate on => on -> [(on, on -> on)]Source

The one depth version of contexts

 propChildren x = children x == map fst (holes x)
 propId x = all (== x) [b a | (a,b) <- holes x]

para :: Uniplate on => (on -> [r] -> r) -> on -> rSource

Perform a fold-like computation on each value, technically a paramorphism

Multiple Type Operations

Queries

universeBi :: Biplate from to => from -> [to]Source

childrenBi :: Biplate from to => from -> [to]Source

Return the children of a type. If to == from then it returns the original element (in contrast to children)

Transformations

transformBi :: Biplate from to => (to -> to) -> from -> fromSource

transformBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m fromSource

rewriteBi :: Biplate from to => (to -> Maybe to) -> from -> fromSource

rewriteBiM :: (Monad m, Biplate from to) => (to -> m (Maybe to)) -> from -> m fromSource

Others

contextsBi :: Biplate from to => from -> [(to, to -> from)]Source

holesBi :: Biplate from to => from -> [(to, to -> from)]Source