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

Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Fixplate.Base

Contents

Description

The core types of Fixplate.

Synopsis

Documentation

newtype Mu f Source

The fixed-point type.

Constructors

Fix 

Fields

unFix :: f (Mu f)
 

Instances

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

isAtom :: Foldable f => Mu f -> Bool Source

We call a tree "atomic" if it has no subtrees.

Annotations

data Ann f a b Source

Type of annotations

Constructors

Ann 

Fields

attr :: a

the annotation

unAnn :: f b

the original functor

Instances

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

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) Source

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

(Eq a, Eq (f b)) => Eq (Ann f a b) Source 
(Ord a, Ord (f b)) => Ord (Ann f a b) Source 
(Show a, Show (f b)) => Show (Ann f a b) Source 

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

Annotated fixed-point type. Equivalent to CoFree f a

liftAnn :: (f e -> g e) -> Ann f a e -> Ann g a e Source

Lifting natural transformations to annotations.

Co-annotations

data CoAnn f a b Source

Categorical dual of Ann.

Constructors

Pure a 
CoAnn (f b) 

Instances

Functor f => Functor (CoAnn f a) Source 
Foldable f => Foldable (CoAnn f a) Source 
Traversable f => Traversable (CoAnn f a) Source 
(Show a, ShowF f) => ShowF (CoAnn f a) Source 
(Ord a, OrdF f) => OrdF (CoAnn f a) Source 
(Eq a, EqF f) => EqF (CoAnn f a) Source 
(Eq a, Eq (f b)) => Eq (CoAnn f a b) Source 
(Ord a, Ord (f b)) => Ord (CoAnn f a b) Source 
(Show a, Show (f b)) => Show (CoAnn f a b) Source 

type CoAttr f a = Mu (CoAnn f a) Source

Categorical dual of Attr. Equivalent to Free f a

liftCoAnn :: (f e -> g e) -> CoAnn f a e -> CoAnn g a e Source

Lifting natural transformations to annotations.

Annotated trees

attribute :: Attr f a -> a Source

The attribute of the root node.

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

A function forgetting all the attributes from an annotated tree.

Holes

data Hole Source

This a data type defined to be a place-holder for childs. It is used in tree drawing, hashing, and Shape.

It is deliberately not made an instance of Show, so that you can choose your preferred style. For example, an acceptable choice is

instance Show Hole where show _ = "_"

Constructors

Hole 

Instances

Higher-order type classes

class EqF f where Source

"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 -> Bool Source

Instances

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

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

(EqF f, EqF g) => EqF ((:*:) f g) Source 
(EqF f, EqF g) => EqF ((:+:) f g) Source 
(Eq hash, EqF f) => EqF (HashAnn hash f) Source 

class EqF f => OrdF f where Source

Methods

compareF :: Ord a => f a -> f a -> Ordering Source

Instances

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

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.

(OrdF f, OrdF g) => OrdF ((:*:) f g) Source 
(OrdF f, OrdF g) => OrdF ((:+:) f g) Source 
(Ord hash, OrdF f) => OrdF (HashAnn hash f) Source 

class ShowF f where Source

Methods

showsPrecF :: Show a => Int -> f a -> ShowS Source

Instances

(Show a, ShowF f) => ShowF (CoAnn f a) Source 
(Show a, ShowF f) => ShowF (Ann f a) Source 
(ShowF f, ShowF g) => ShowF ((:*:) f g) Source 
(ShowF f, ShowF g) => ShowF ((:+:) f g) Source 
(ShowF f, Show hash) => ShowF (HashAnn hash f) Source 

class ReadF f where Source

Methods

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

Instances

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

showF :: (ShowF f, Show a) => f a -> String Source

showsF :: (ShowF f, Show a) => f a -> ShowS Source

Attrib (cofree comonad)

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 (and Comonad). This is necessary since Haskell does not allow partial application of type synonyms.

Equivalent to the co-free comonad.

Constructors

Attrib 

Fields

unAttrib :: Attr f a
 

CoAttrib (free monad)

newtype CoAttrib f a Source

Categorial dual of Attrib. Equivalent to the free monad.

Constructors

CoAttrib 

Fields

unCoAttrib :: CoAttr f a