ideas-1.1: Feedback services for intelligent tutoring systems

Portabilityportable (depends on ghc)
Stabilityprovisional
Maintainerbastiaan.heeren@ou.nl
Safe HaskellNone

Ideas.Common.Utils.Uniplate

Contents

Description

Exports a subset of Data.Generics.Uniplate.Direct (the Uniplate type class and its utility plus constructor functions)

Synopsis

Uniplate type class and utility functions

class Uniplate on where

The standard Uniplate class, all operations require this. All definitions must define uniplate, while descend and descendM are optional.

Methods

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

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 -> on

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. This function can be defined explicitly, or can be provided by automatically in terms of uniplate.

For example, on the sample type, we could write:

 descend f (Val i  ) = Val i
 descend f (Neg a  ) = Neg (f a)
 descend f (Add a b) = Add (f a) (f b)

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

Monadic variant of descend

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

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

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

Return all the contexts and holes.

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

descend :: Uniplate on => (on -> on) -> on -> on

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. This function can be defined explicitly, or can be provided by automatically in terms of uniplate.

For example, on the sample type, we could write:

 descend f (Val i  ) = Val i
 descend f (Neg a  ) = Neg (f a)
 descend f (Add a b) = Add (f a) (f b)

descendM :: Uniplate on => forall m. Monad m => (on -> m on) -> on -> m on

Monadic variant of descend

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

The one depth version of contexts

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

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

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

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

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 on

Monadic variant of rewrite

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

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 on

Monadic variant of transform

uniplate :: Uniplate on => on -> (Str on, Str on -> on)

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)

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

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]

Instance constructors

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

The field to the right does not contain the target.

(|*) :: Type (to -> from) to -> to -> Type from to

The field to the right is the target.

(||*) :: Type ([to] -> from) to -> [to] -> Type from to

The field to the right is a list of the type of the target

plate :: from -> Type from to

The main combinator used to start the chain.

The following rule can be used for optimisation:

 plate Ctor |- x == plate (Ctor x)