Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class MakeBaseFunctor a where
- makeBaseFunctor :: a -> DecsQ
- makeBaseFunctorWith :: BaseRules -> a -> DecsQ
- data BaseRules
- baseRules :: BaseRules
- baseRulesType :: Functor f => ((Name -> Name) -> f (Name -> Name)) -> BaseRules -> f BaseRules
- baseRulesCon :: Functor f => ((Name -> Name) -> f (Name -> Name)) -> BaseRules -> f BaseRules
- baseRulesField :: Functor f => ((Name -> Name) -> f (Name -> Name)) -> BaseRules -> f BaseRules
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 instanceBase
(Expr a) = ExprF a instanceRecursive
(Expr a) whereproject
(Lit x) = LitF xproject
(Add x y) = AddF x yproject
(x :* y) = x :*$ y instanceCorecursive
(Expr a) whereembed
(LitF x) = Lit xembed
(AddF x y) = Add x yembed
(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 Name
s and Dec
s 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 instanceBase
(Rose f a) = RoseF f a instance Functor f =>Recursive
(Rose f a) whereproject
(Rose x xs) = RoseF x xs instance Functor f =>Corecursive
(Rose f a) whereembed
(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
makeBaseFunctor :: a -> DecsQ Source #
makeBaseFunctorWith :: BaseRules -> a -> DecsQ Source #
Build base functor with a custom configuration.
Instances
MakeBaseFunctor Dec Source # | Expects declarations of makeBaseFunctor [d| instance Functor f => Recursive (Rose f a) |] This way we can provide a context for generated instances.
Note that this instance's |
Defined in Data.Functor.Foldable.TH | |
MakeBaseFunctor Name Source # | |
Defined in Data.Functor.Foldable.TH | |
MakeBaseFunctor a => MakeBaseFunctor [a] Source # | |
Defined in Data.Functor.Foldable.TH makeBaseFunctor :: [a] -> DecsQ Source # makeBaseFunctorWith :: BaseRules -> [a] -> DecsQ Source # | |
MakeBaseFunctor a => MakeBaseFunctor (Q a) Source # | |
Defined in Data.Functor.Foldable.TH |
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 $
.