Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Generics.Genifunctors
Description
Generate (derive) generalized fmap
, foldMap
and traverse
for Bifunctors, Trifunctors, or a functor with any arity
Example:
data U a b c d = L [U a b c d] -- polymorphic recursion | M (V (a,b) (Either c d)) -- mutually recursive | a :+: Int -- infix syntax, record syntax, type synonyms | R { c :: c, d :: String } -- and primitive data types supported data V u v = X (U v v u u) | Z u fmapU :: (a -> a') -> (b -> b') -> (c -> c') -> (d -> d') -> U a b c d -> U a' b' c' d' fmapU = $(genFmap ''U) foldU :: Monoid m => (a -> m) -> (b -> m) -> (c -> m) -> (d -> m) -> U a b c d -> m foldU = $(genFoldMap ''U) travU :: Applicative f => (a -> f a') -> (b -> f b') -> (c -> f c') -> (d -> f d') -> U a b c d -> f (U a' b' c' d') travU = $(genTraverse ''U)
genFoldMapT
and genTraverseT
allow for specifying custom functions to handle
subparts of a specific type. The compiler will throw an error if any of the
types is actually a type synonym.
Documentation
genFmap :: Name -> Q Exp Source #
Generate generalized fmap
for a type
bimapTuple :: (a -> a') -> (b -> b') -> (a,b) -> (a',b') bimapTuple = $(genFmap ''(,))
genFoldMap :: Name -> Q Exp Source #
Generate generalized foldMap
for a type
foldMapEither :: Monoid m => (a -> m) -> (b -> m) -> Either a b -> m foldMapEither = $(genFoldMap ''Either)
genFoldMapT :: [(Name, Name)] -> Name -> Q Exp Source #
Generate generalized foldMap
for a type, optionally traversing
subparts of it with custom implementations.
foldTupleRev :: Monoid m => (a -> m) -> (b -> m) -> (a,b) -> m foldTupleRev f g (a,b) = g b <> f a foldUCustom :: Monoid m => (a -> m) -> (b -> m) -> (c -> m) -> (d -> m) -> U a b c d -> m foldUCustom = $(genFoldMapT [(''(,), 'foldTupleRev)] ''U)
genTraverse :: Name -> Q Exp Source #
Generate generalized traversable
for a type
travTriple :: Applicative f => (a -> f a') -> (b -> f b') -> (c -> f c') -> (a,b,c) -> f (a',b',c') travTriple = $(genTraverse ''(,,))
genTraverseT :: [(Name, Name)] -> Name -> Q Exp Source #
Generate generalized traversable
for a type, optionally traversing
subparts of it with custom implementations.
travTupleRev :: Applicative f => (a -> f a') -> (b -> f b') -> (a,b) -> f (a',b') travTupleRev f g (a,b) = (\b a -> (a,b)) <$> g b <*> f a travUCustom :: Applicative f => (a -> f a') -> (b -> f b') -> (c -> f c') -> (d -> f d') -> U a b c d -> f (U a' b' c' d') travUCustom = $(genTraverseT [(''(,), 'travTupleRev), (''V, 'travVCustom)] ''U) travVCustom :: Applicative f => (a -> f a') -> (b -> f b') -> V a b -> f (V a' b') travVCustom = $(genTraverseT [(''U, 'travUCustom)] ''V)