Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- module Data.Generics.Uniplate.Operations
- plate :: from -> Type from to
- plateSelf :: to -> Type to to
- (|+) :: Biplate item to => Type (item -> from) to -> item -> Type from to
- (|-) :: Type (item -> from) to -> item -> Type from to
- (|*) :: Type (to -> from) to -> to -> Type from to
- (||+) :: Biplate item to => Type ([item] -> from) to -> [item] -> Type from to
- (||*) :: Type ([to] -> from) to -> [to] -> Type from to
- plateProject :: Biplate item to => (from -> item) -> (item -> from) -> from -> Type from to
Documentation
The Combinators
plate :: from -> Type from to Source #
The main combinator used to start the chain.
The following rule can be used for optimisation:
plate Ctor |- x == plate (Ctor x)
(|+) :: Biplate 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.
(||+) :: Biplate item to => Type ([item] -> from) to -> [item] -> Type from to Source #
The field to the right is a list of types which may contain the target
(||*) :: Type ([to] -> from) to -> [to] -> Type from to Source #
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 to Source #
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
Orphan instances
Uniplate Bool Source # | |
Uniplate Char Source # | |
Uniplate Double Source # | |
Uniplate Float Source # | |
Uniplate Int Source # | |
Uniplate Integer Source # | |
Uniplate () Source # | |
Uniplate [Char] Source # | |
Uniplate (Ratio Integer) Source # | |
Biplate [Char] Char Source # | |
Biplate (Ratio Integer) Integer Source # | |
Biplate [Char] [Char] Source # | |
Biplate (Ratio Integer) (Ratio Integer) Source # | |