-- | This library provides Uniplate-style generic traversals for fixed-point types. -- The advantages of using fixed-point types instead of explicit recursion are the following: -- -- * we can 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; -- -- * some operations can retain the structure of the tree, instead flattening -- it into a list; -- -- * it is quite straightforward to provide a generic zipper. -- -- 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: -- -- > Expr -- > = Kst Int -- > | Var String -- > | Add Expr Expr -- > deriving (Eq,Show) -- -- We can open up the recursion, and obtain a /functor/ instead: -- -- > 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@. -- -- This module re-exports most of the functionality present in the library. -- -- The library should be fully Haskell98 compatible, with the exception -- of the module "Data.Generics.Fixplate.Structure", which needs -- the @Rank2Types@ extension. For compatibility, the functionality -- of this module is at the moment only provided when compiled with GHC or Hugs. -- 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.Structure , 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.Structure import Data.Foldable import Data.Traversable --------------------------------------------------------------------------------