uniplate-1.6.8: Help writing simple, concise and fast generic operations.

Safe HaskellNone

Data.Generics.Uniplate.Direct

Contents

Description

This module supplies a method for writing Uniplate and Biplate instances. This moulde gives the highest performance, but requires many instance definitions. The instances can be generated using Derive: http://community.haskell.org/~ndm/derive/.

To take an example:

 data Expr = Var Int | Pos Expr String | Neg Expr | Add Expr Expr
 data Stmt = Seq [Stmt] | Sel [Expr] | Let String Expr

 instance Uniplate Expr where
     uniplate (Var x  ) = plate Var |- x
     uniplate (Pos x y) = plate Pos |* x |- y
     uniplate (Neg x  ) = plate Neg |* x
     uniplate (Add x y) = plate Add |* x |* y

 instance Biplate Expr Expr where
     biplate = plateSelf

 instance Uniplate Stmt where
     uniplate (Seq x  ) = plate Seq ||* x
     uniplate (Sel x  ) = plate Sel ||+ x
     uniplate (Let x y) = plate Let |-  x |- y

 instance Biplate Stmt Stmt where
     biplate = plateSelf

 instance Biplate Stmt Expr where
     biplate (Seq x  ) = plate Seq ||+ x
     biplate (Sel x  ) = plate Sel ||* x
     biplate (Let x y) = plate Let |-  x |* y

To define instances for abstract data types, such as Map or Set from the containers package, use plateProject.

This module provides a few monomorphic instances of Uniplate / Biplate for common types available in the base library, but does not provide any polymorphic instances. Given only monomorphic instances it is trivial to ensure that all instances are disjoint, making it easier to add your own instances.

When defining polymorphic instances, be carefully to mention all potential children. Consider Biplate Int (Int, a) - this instance cannot be correct because it will fail to return both Int values on (Int,Int). There are some legitimate polymorphic instances, such as Biplate a [a] and Biplate a a, but take care to avoid overlapping instances.

Synopsis

Documentation

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)

plateSelf :: to -> Type to toSource

Used for Biplate definitions where both types are the same.

(|+) :: Biplate item to => Type (item -> from) to -> item -> Type from toSource

The field to the right may contain the target.

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

The field to the right does not contain the target.

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

The field to the right is the target.

(||+) :: Biplate item to => Type ([item] -> from) to -> [item] -> Type from toSource

The field to the right is a list of types which may contain the target

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

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

plateProject :: Biplate item to => (from -> item) -> (item -> from) -> from -> Type from toSource

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

 instance Biplate (Map.Map [Char] Int) Char where
     biplate = plateProject Map.toList Map.fromList

If the types ensure that no operations will not change the keys we can use the fromDistictAscList function to reconstruct the Map:

 instance Biplate (Map.Map [Char] Int) Int where
     biplate = plateProject Map.toAscList Map.fromDistinctAscList