Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This library provides Uniplate-style generic traversals and other recursion schemes for fixed-point types. There are many advantages of using fixed-point types instead of explicit recursion:
- we can easily add attributes to the nodes of an existing tree;
- there is no need for a custom type class, we can build everything on the top of
Functor
,Foldable
andTraversable
, for which GHC can derive the instances for us; - we can provide interesting recursion schemes
- some operations can retain the structure of the tree, instead flattening it into a list;
- it is relatively straightforward to provide generic implementations of the zipper, tries, tree drawing, hashing, etc...
The main disadvantage is that it does not work well for mutually recursive data types, and that pattern matching becomes more tedious (but there are partial solutions for the latter).
Consider as an example the following simple expression language, encoded by a recursive algebraic data type:
data Expr = Kst Int | Var String | Add Expr Expr deriving (Eq,Show)
We can open up the recursion, and obtain a functor instead:
data Expr1 e = Kst Int | Var String | Add e e deriving (Eq,Show,Functor,Foldable,Traversable)
The fixed-point type Mu
Expr1
is isomorphic to Expr
.
However, we can also add some attributes to the nodes:
The type Attr
Expr1 a =
Mu
(
Ann
Expr1 a)
is the type of
with the same structure, but with each node having an extra
field of type a
.
The functions in this library work on types like that: Mu
f
,
where f
is a functor, and sometimes explicitely on Attr
f a
.
The organization of the modules (excluding Util.*) is the following:
- Data.Generics.Fixplate.Base - core types and type classes
- Data.Generics.Fixplate.Functor - sum and product functors
- Data.Generics.Fixplate.Traversals - Uniplate-style traversals
- Data.Generics.Fixplate.Morphisms - recursion schemes
- Data.Generics.Fixplate.Attributes - annotated trees
- Data.Generics.Fixplate.Open - functions operating on functors
- Data.Generics.Fixplate.Zipper - generic zipper
- Data.Generics.Fixplate.Draw - generic tree drawing (both ASCII and graphviz)
- Data.Generics.Fixplate.Pretty - pretty-printing of expression trees
- Data.Generics.Fixplate.Trie - generic generalized tries
- Data.Generics.Fixplate.Hash - annotating trees with their hashes
This module re-exports the most common functionality present in the library (but not for example the zipper, tries, hashing).
The library itself should be fully Haskell98 compatible; no language extensions are used. The only exception is the Data.Generics.Fixplate.Functor module, which uses the TypeOperators language extension for syntactic convenience (but this is not used anywhere else).
Note: to obtain Eq
, Ord
, Show
, Read
and other instances for
fixed point types like Mu Expr1
, consult the documentation of the
EqF
type class (cf. the related OrdF
, ShowF
and ReadF
classes)
- module Data.Generics.Fixplate.Base
- module Data.Generics.Fixplate.Traversals
- module Data.Generics.Fixplate.Morphisms
- module Data.Generics.Fixplate.Attributes
- module Data.Generics.Fixplate.Draw
- class Functor f where
- class Foldable t where
- foldMap :: Monoid m => (a -> m) -> t a -> m
- foldr :: (a -> b -> b) -> b -> t a -> b
- foldl :: (b -> a -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> t a -> a
- foldl1 :: (a -> a -> a) -> t a -> a
- null :: t a -> Bool
- length :: t a -> Int
- elem :: Eq a => a -> t a -> Bool
- maximum :: Ord a => t a -> a
- minimum :: Ord a => t a -> a
- sum :: Num a => t a -> a
- product :: Num a => t a -> a
- class (Functor t, Foldable t) => Traversable t where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
Documentation
module Data.Generics.Fixplate.Base
module Data.Generics.Fixplate.Draw
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
Data structures that can be folded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Foldable Tree where foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
This is suitable even for abstract types, as the monoid is assumed
to satisfy the monoid laws. Alternatively, one could define foldr
:
instance Foldable Tree where foldr f z Empty = z foldr f z (Leaf x) = f x z foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
sum
, product
, maximum
, and minimum
should all be essentially
equivalent to foldMap
forms, such as
sum = getSum . foldMap Sum
but may be less defined.
If the type is also a Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
Foldable [] | |
Foldable Maybe | |
Foldable V1 | |
Foldable U1 | |
Foldable Par1 | |
Foldable ZipList | |
Foldable Dual | |
Foldable Sum | |
Foldable Product | |
Foldable First | |
Foldable Last | |
Foldable (Either a) | |
Foldable f => Foldable (Rec1 f) | |
Foldable (URec Char) | |
Foldable (URec Double) | |
Foldable (URec Float) | |
Foldable (URec Int) | |
Foldable (URec Word) | |
Foldable (URec (Ptr ())) | |
Foldable ((,) a) | |
Foldable (Array i) | |
Foldable (Proxy *) | |
Foldable (Map k) | |
Foldable f => Foldable (CoAttrib f) # | |
Foldable f => Foldable (Attrib f) # | |
Foldable (K1 i c) | |
(Foldable f, Foldable g) => Foldable ((:+:) f g) | |
(Foldable f, Foldable g) => Foldable ((:*:) f g) | |
(Foldable f, Foldable g) => Foldable ((:.:) f g) | |
Foldable (Const * m) | |
Foldable f => Foldable (CoAnn f a) # | |
Foldable f => Foldable (Ann f a) # | |
(Foldable f, Foldable g) => Foldable ((:*:) f g) # | |
(Foldable f, Foldable g) => Foldable ((:+:) f g) # | |
Foldable f => Foldable (HashAnn hash f) # | |
Foldable f => Foldable (M1 i c f) | |
class (Functor t, Foldable t) => Traversable t where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse
must satisfy the following laws:
- naturality
t .
for every applicative transformationtraverse
f =traverse
(t . f)t
- identity
traverse
Identity = Identity- composition
traverse
(Compose .fmap
g . f) = Compose .fmap
(traverse
g) .traverse
f
A definition of sequenceA
must satisfy the following laws:
- naturality
t .
for every applicative transformationsequenceA
=sequenceA
.fmap
tt
- identity
sequenceA
.fmap
Identity = Identity- composition
sequenceA
.fmap
Compose = Compose .fmap
sequenceA
.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative
operations, i.e.
and the identity functor Identity
and composition of functors Compose
are defined as
newtype Identity a = Identity a instance Functor Identity where fmap f (Identity x) = Identity (f x) instance Applicative Identity where pure x = Identity x Identity f <*> Identity x = Identity (f x) newtype Compose f g a = Compose (f (g a)) instance (Functor f, Functor g) => Functor (Compose f g) where fmap f (Compose x) = Compose (fmap (fmap f) x) instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure x = Compose (pure (pure x)) Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
(The naturality law is implied by parametricity.)
Instances are similar to Functor
, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).