Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Generic.Data.Function.FoldMap
Description
foldMap
for generic data types.
foldMap
can be considered a two-step process:
Applying this to generic data types:
Field mappings are handled using a per-monoid type class. You need a monoid m
with an associated type class which has a function a -> m
. Write a
GenericFoldMap
instance for your monoid which points to your type class. If a
field type doesn't have a matching instance, the generic instance emits a type
error.
Sum types (with multiple constructors) are handled by (<>)
-ing the constructor
with its contents (in that order). You must provide a String -> m
function for
mapping constructor names. If you need custom sum type handling, you may write
your own and still leverage the individual constructor generics.
This function can provide generic support for simple fold-y operations like serialization.
Synopsis
- class GenericFoldMap tag where
- type GenericFoldMapM tag :: Type
- type GenericFoldMapC tag a :: Constraint
- genericFoldMapF :: GenericFoldMapC tag a => a -> GenericFoldMapM tag
- genericFoldMapNonSum :: forall tag a. (Generic a, GFoldMapNonSum tag (Rep a)) => a -> GenericFoldMapM tag
- class GFoldMapNonSum tag gf
- genericFoldMapSum :: forall tag sumtag a. (Generic a, GFoldMapSum tag sumtag (Rep a)) => ParseCstrTo sumtag (GenericFoldMapM tag) -> a -> GenericFoldMapM tag
- class GFoldMapSum tag sumtag gf
- genericFoldMapSumRaw :: forall tag a. (Generic a, GFoldMapSum tag Raw (Rep a)) => (String -> GenericFoldMapM tag) -> a -> GenericFoldMapM tag
- genericFoldMapSumConsByte :: forall tag a. (Generic a, GFoldMapSumConsByte tag (Rep a)) => (Word8 -> GenericFoldMapM tag) -> a -> GenericFoldMapM tag
- class GFoldMapSumConsByte tag f
Documentation
class GenericFoldMap tag where Source #
Implementation enumeration type class for generic foldMap
.
The type variable is uninstantiated, used purely as a tag. Good types include the type class used inside (providing you define the type class/it's not an orphan instance), or a custom void data type. See the binrep library on Hackage for an example.
Associated Types
type GenericFoldMapM tag :: Type Source #
type GenericFoldMapC tag a :: Constraint Source #
The type class providing the map function in foldMap
for permitted
types.
Methods
genericFoldMapF :: GenericFoldMapC tag a => a -> GenericFoldMapM tag Source #
The map function in foldMap
(first argument).
Instances
GenericFoldMap Showly Source # | |
Defined in Generic.Data.Function.Example Methods genericFoldMapF :: GenericFoldMapC Showly a => a -> GenericFoldMapM Showly Source # | |
Monoid m => GenericFoldMap (EmptyRec0 m :: Type) Source # | |
Defined in Generic.Data.Function.FoldMap.Constructor Associated Types type GenericFoldMapM (EmptyRec0 m) Source # type GenericFoldMapC (EmptyRec0 m) a Source # Methods genericFoldMapF :: GenericFoldMapC (EmptyRec0 m) a => a -> GenericFoldMapM (EmptyRec0 m) Source # | |
GenericFoldMap (NoRec0 m :: Type) Source # |
|
Defined in Generic.Data.Function.FoldMap.Constructor Methods genericFoldMapF :: GenericFoldMapC (NoRec0 m) a => a -> GenericFoldMapM (NoRec0 m) Source # |
genericFoldMapNonSum :: forall tag a. (Generic a, GFoldMapNonSum tag (Rep a)) => a -> GenericFoldMapM tag Source #
Generic foldMap
over a term of non-sum data type a
.
a
must have exactly one constructor.
class GFoldMapNonSum tag gf Source #
foldMap
over generic product data types.
Take a generic representation, map each field in the data type to a Monoid
,
and combine the results with (<>
).
Minimal complete definition
Instances
GFoldMapNonSum (tag :: k1) (V1 :: k2 -> Type) Source # | |
Defined in Generic.Data.Function.FoldMap.NonSum Methods gFoldMapNonSum :: forall (p :: k10). V1 p -> GenericFoldMapM tag Source # | |
GFoldMapNonSum (tag :: k1) (l :+: r :: k2 -> Type) Source # | |
Defined in Generic.Data.Function.FoldMap.NonSum Methods gFoldMapNonSum :: forall (p :: k10). (l :+: r) p -> GenericFoldMapM tag Source # | |
GFoldMapC tag gf => GFoldMapNonSum (tag :: k1) (C1 c gf :: k2 -> Type) Source # | |
Defined in Generic.Data.Function.FoldMap.NonSum Methods gFoldMapNonSum :: forall (p :: k10). C1 c gf p -> GenericFoldMapM tag Source # | |
GFoldMapNonSum tag gf => GFoldMapNonSum (tag :: k1) (D1 c gf :: k2 -> Type) Source # | |
Defined in Generic.Data.Function.FoldMap.NonSum Methods gFoldMapNonSum :: forall (p :: k10). D1 c gf p -> GenericFoldMapM tag Source # |
genericFoldMapSum :: forall tag sumtag a. (Generic a, GFoldMapSum tag sumtag (Rep a)) => ParseCstrTo sumtag (GenericFoldMapM tag) -> a -> GenericFoldMapM tag Source #
Generic foldMap
over a term of sum data type a
.
You must provide a type tag for parsing constructor names on the type-level, and a function for reifying such results to monoidal values.
class GFoldMapSum tag sumtag gf Source #
Minimal complete definition
Instances
GFoldMapSumD tag sumtag dtName gf => GFoldMapSum (tag :: k1) (sumtag :: k2) (D1 ('MetaData dtName _md2 _md3 _md4) gf :: k3 -> Type) Source # | |
Defined in Generic.Data.Function.FoldMap.Sum Methods gFoldMapSum :: forall (p :: k20). ParseCstrTo sumtag (GenericFoldMapM tag) -> D1 ('MetaData dtName _md2 _md3 _md4) gf p -> GenericFoldMapM tag Source # |
genericFoldMapSumRaw :: forall tag a. (Generic a, GFoldMapSum tag Raw (Rep a)) => (String -> GenericFoldMapM tag) -> a -> GenericFoldMapM tag Source #
Generic foldMap
over a term of sum data type a
.
You must provide a function for mapping constructor names to monoidal values.
genericFoldMapSumConsByte :: forall tag a. (Generic a, GFoldMapSumConsByte tag (Rep a)) => (Word8 -> GenericFoldMapM tag) -> a -> GenericFoldMapM tag Source #
Generic foldMap
over a term of sum data type a
where constructors are
mapped to their index (distance from first/leftmost constructor)
a
must have at least two constructors.
You must provide a function for mapping bytes to monoidal values.
This should be fairly fast, but sadly I think it's slower than the generics in store and binary/cereal libraries.
class GFoldMapSumConsByte tag f Source #
Minimal complete definition