micro-recursion-schemes-5.0.2.1: Simple recursion schemes

Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Foldable.TH

Synopsis

Documentation

makeBaseFunctor :: Name -> DecsQ Source #

Build base functor with a sensible default configuration.

e.g.

data Expr a
    = Lit a
    | Add (Expr a) (Expr a)
    | Expr a :* [Expr a]
  deriving (Show)

makeBaseFunctor ''Expr

will create

data ExprF a x
    = LitF a
    | AddF x x
    | x :*$ [x]
  deriving (Functor, Foldable, Traversable)

type instance Base (Expr a) = ExprF a

instance Recursive (Expr a) where
    project (Lit x)   = LitF x
    project (Add x y) = AddF x y
    project (x :* y)  = x :*$ y

instance Corecursive (Expr a) where
    embed (LitF x)   = Lit x
    embed (AddF x y) = Add x y
    embed (x :*$ y)  = x :*$ y
makeBaseFunctor = makeBaseFunctorWith baseRules

Notes:

makeBaseFunctor works properly only with ADTs. Existentials and GADTs aren't supported, as we don't try to do better than GHC's DeriveFunctor.

makeBaseFunctorWith :: BaseRules -> Name -> DecsQ Source #

Build base functor with a custom configuration.

data BaseRules Source #

Rules of renaming data names

baseRules :: BaseRules Source #

Default BaseRules: append F or $ to data type, constructors and field names.

baseRulesType :: Functor f => ((Name -> Name) -> f (Name -> Name)) -> BaseRules -> f BaseRules Source #

How to name the base functor type.

Default is to append F or $.

baseRulesCon :: Functor f => ((Name -> Name) -> f (Name -> Name)) -> BaseRules -> f BaseRules Source #

How to rename the base functor type constructors.

Default is to append F or $.

baseRulesField :: Functor f => ((Name -> Name) -> f (Name -> Name)) -> BaseRules -> f BaseRules Source #

How to rename the base functor type field names (in records).

Default is to append F or $.