-- | 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' and 'Traversable', 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 ( module Data.Generics.Fixplate.Base , module Data.Generics.Fixplate.Traversals , module Data.Generics.Fixplate.Morphisms , module Data.Generics.Fixplate.Attributes -- , module Data.Generics.Fixplate.Zipper , module Data.Generics.Fixplate.Draw , Functor(..) , Foldable(..) , Traversable(..) ) where -------------------------------------------------------------------------------- import Data.Generics.Fixplate.Base import Data.Generics.Fixplate.Traversals import Data.Generics.Fixplate.Morphisms import Data.Generics.Fixplate.Attributes -- import Data.Generics.Fixplate.Zipper import Data.Generics.Fixplate.Draw import Data.Foldable () import Data.Traversable () --------------------------------------------------------------------------------