recursion-schemes-5.2.2.4: Representing common recursion patterns as higher-order functions
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Foldable.TH

Synopsis

Documentation

class MakeBaseFunctor a where 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

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.

Allowing makeBaseFunctor to take both Names and Decs as an argument is why it exists as a method in a type class. For trickier data-types, like rose-tree (see also Cofree):

data Rose f a = Rose a (f (Rose f a))

we can invoke makeBaseFunctor with an instance declaration to provide needed context for instances. (c.f. StandaloneDeriving)

makeBaseFunctor [d| instance Functor f => Recursive (Rose f a) |]

will create

data RoseF f a r = RoseF a (f fr)
  deriving (Functor, Foldable, Traversable)

type instance Base (Rose f a) = RoseF f a

instance Functor f => Recursive (Rose f a) where
  project (Rose x xs) = RoseF x xs

instance Functor f => Corecursive (Rose f a) where
  embed (RoseF x xs) = Rose x xs

Some doctests:

>>> data Expr a = Lit a | Add (Expr a) (Expr a) | Expr a :* [Expr a]; makeBaseFunctor ''Expr
>>> :t AddF
AddF :: r -> r -> ExprF a r
>>> data Rose f a = Rose a (f (Rose f a)); makeBaseFunctor $ asQ [d| instance Functor f => Recursive (Rose f a) |]
>>> :t RoseF
RoseF :: a -> f r -> RoseF f a r
>>> let rose = Rose 1 (Just (Rose 2 (Just (Rose 3 Nothing))))
>>> cata (\(RoseF x f) -> x + maybe 0 id f) rose
6

Minimal complete definition

makeBaseFunctorWith

Methods

makeBaseFunctor :: a -> DecsQ Source #

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

Build base functor with a custom configuration.

Instances

Instances details
MakeBaseFunctor Dec Source #

Expects declarations of Recursive or Corecursive instances, e.g.

makeBaseFunctor [d| instance Functor f => Recursive (Rose f a) |]

This way we can provide a context for generated instances. Note that this instance's makeBaseFunctor still generates all of Base type instance, Recursive and Corecursive instances.

Instance details

Defined in Data.Functor.Foldable.TH

MakeBaseFunctor Name Source # 
Instance details

Defined in Data.Functor.Foldable.TH

MakeBaseFunctor a => MakeBaseFunctor [a] Source # 
Instance details

Defined in Data.Functor.Foldable.TH

MakeBaseFunctor a => MakeBaseFunctor (Q a) Source # 
Instance details

Defined in Data.Functor.Foldable.TH

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 $.