fixplate-0.1.3: Uniplate-style generic traversals for optionally annotated fixed-point types.

Safe HaskellSafe-Infered

Data.Generics.Fixplate.Base

Description

The core types of Fixplate.

Synopsis

Documentation

attribute :: Attr f a -> aSource

The attribute of the root node.

forget :: Functor f => Attr f a -> Mu fSource

A function forgetting all the attributes from an annotated tree.

newtype Mu f Source

The fixed-point type.

Constructors

Fix 

Fields

unFix :: f (Mu f)
 

Instances

EqF f => Eq (Mu f) 
OrdF f => Ord (Mu f) 
ReadF f => Read (Mu f) 
ShowF f => Show (Mu f) 

data Ann f a b Source

Annotated functors.

Constructors

Ann 

Fields

attr :: a

the annotation

unAnn :: f b

the original functor

Instances

Functor f => Functor (Ann f a) 
Foldable f => Foldable (Ann f a) 
Traversable f => Traversable (Ann f a) 
(Read a, ReadF f) => ReadF (Ann f a) 
(Show a, ShowF f) => ShowF (Ann f a) 
(Ord a, OrdF f) => OrdF (Ann f a)

NOTE: The OrdF instance for annotations first compares the annotations, and then the functor part. If this is not the desired behaviour (it's not clear to me at the moment what is the good default here), you can use the standard newtype trick to define a new behaviour.

(Eq a, EqF f) => EqF (Ann f a)

NOTE: The EqF instance for annotations compares both the annotations and the original part.

type Attr f a = Mu (Ann f a)Source

Annotated fixed-point type.

class EqF f whereSource

"Functorised" versions of standard type classes. If you have your a structure functor, for example

 Expr e 
   = Kst Int 
   | Var String 
   | Add e e 
   deriving (Eq,Ord,Read,Show,Functor,Foldable,Traversable)

you should make it an instance of these, so that the fixed-point type Mu Expr can be an instance of Eq, Ord and Show. Doing so is very easy:

 instance EqF   Expr where equalF     = (==)
 instance OrdF  Expr where compareF   = compare
 instance ShowF Expr where showsPrecF = showsPrec

The Read instance depends on whether we are using GHC or not. The Haskell98 version is

 instance ReadF Expr where readsPrecF = readsPrec

while the GHC version is

 instance ReadF Expr where readPrecF  = readPrec

Methods

equalF :: Eq a => f a -> f a -> BoolSource

Instances

(Eq a, EqF f) => EqF (Ann f a)

NOTE: The EqF instance for annotations compares both the annotations and the original part.

class EqF f => OrdF f whereSource

Methods

compareF :: Ord a => f a -> f a -> OrderingSource

Instances

(Ord a, OrdF f) => OrdF (Ann f a)

NOTE: The OrdF instance for annotations first compares the annotations, and then the functor part. If this is not the desired behaviour (it's not clear to me at the moment what is the good default here), you can use the standard newtype trick to define a new behaviour.

class ShowF f whereSource

Methods

showsPrecF :: Show a => Int -> f a -> ShowSSource

Instances

(Show a, ShowF f) => ShowF (Ann f a) 

class ReadF f whereSource

Methods

readPrecF :: Read a => ReadPrec (f a)Source

Instances

(Read a, ReadF f) => ReadF (Ann f a) 

newtype Attrib f a Source

A newtype wrapper around Attr f a so that we can make Attr f an instance of Functor, Foldable and Traversable. This is necessary since Haskell does not allow partial application of type synonyms.

Constructors

Attrib 

Fields

unAttrib :: Attr f a
 

Instances

Functor f => Functor (Attrib f) 
Foldable f => Foldable (Attrib f) 
Traversable f => Traversable (Attrib f) 
(ShowF f, Show a) => Show (Attrib f a)