generic-data-functions-0.5.1: Familiar functions lifted to generic data types
Safe HaskellSafe-Inferred
LanguageGHC2021

Generic.Data.Function.FoldMap

Description

foldMap for generic data types.

foldMap can be considered a two-step process:

  • map every element a of a t a (where Foldable t) to some Monoid m
  • combine elements using (<>)

Applying this to generic data types:

  • map every field of a constructor to some Monoid m
  • combine elements using (<>)

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

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 #

The target Monoid to foldMap to.

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

Instances details
GenericFoldMap Showly Source # 
Instance details

Defined in Generic.Data.Function.Example

Monoid m => GenericFoldMap (EmptyRec0 m :: Type) Source #

foldMap over types where all fields map to mempty.

Instance details

Defined in Generic.Data.Function.FoldMap.Constructor

Associated Types

type GenericFoldMapM (EmptyRec0 m) Source #

type GenericFoldMapC (EmptyRec0 m) a Source #

GenericFoldMap (NoRec0 m :: Type) Source #

foldMap over types with no fields in any constructor.

Instance details

Defined in Generic.Data.Function.FoldMap.Constructor

Associated Types

type GenericFoldMapM (NoRec0 m) Source #

type GenericFoldMapC (NoRec0 m) a Source #

genericFoldMapNonSum :: forall {k} (tag :: k) 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

gFoldMapNonSum

Instances

Instances details
GFoldMapNonSum (tag :: k1) (V1 :: k2 -> Type) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Generic.Data.Function.FoldMap.NonSum

Methods

gFoldMapNonSum :: forall (p :: k10). D1 c gf p -> GenericFoldMapM tag Source #

genericFoldMapSum :: forall {k} (tag :: k) a. (Generic a, GFoldMapSum tag (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.

This is the most generic option, but depending on your string manipulation may be slower.

class GFoldMapSum tag gf Source #

Minimal complete definition

gFoldMapSum

Instances

Instances details
GFoldMapSum (tag :: k1) (V1 :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.Sum

Methods

gFoldMapSum :: forall (p :: k10). (String -> GenericFoldMapM tag) -> V1 p -> GenericFoldMapM tag Source #

GFoldMapCSum tag (l :+: r) => GFoldMapSum (tag :: k1) (l :+: r :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.Sum

Methods

gFoldMapSum :: forall (p :: k10). (String -> GenericFoldMapM tag) -> (l :+: r) p -> GenericFoldMapM tag Source #

GFoldMapCSum tag (C1 c gf) => GFoldMapSum (tag :: k1) (C1 c gf :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.Sum

Methods

gFoldMapSum :: forall (p :: k10). (String -> GenericFoldMapM tag) -> C1 c gf p -> GenericFoldMapM tag Source #

GFoldMapSum tag gf => GFoldMapSum (tag :: k1) (D1 c gf :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.Sum

Methods

gFoldMapSum :: forall (p :: k10). (String -> GenericFoldMapM tag) -> D1 c gf p -> GenericFoldMapM tag Source #

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

gFoldMapSumConsByte

Instances

Instances details
GFoldMapSumConsByte (m :: k1) (V1 :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

gFoldMapSumConsByte :: forall (p :: k10). (Word8 -> GenericFoldMapM m) -> V1 p -> GenericFoldMapM m Source #

(FitsInByte (SumArity (l :+: r)), GFoldMapCSumCtrArityByte tag 0 (l :+: r), GFoldMapCSumCtr tag (l :+: r), Semigroup (GenericFoldMapM tag)) => GFoldMapSumConsByte (tag :: k) (l :+: r :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

gFoldMapSumConsByte :: forall (p :: k1). (Word8 -> GenericFoldMapM tag) -> (l :+: r) p -> GenericFoldMapM tag Source #

GFoldMapSumConsByte (m :: k1) (C1 c f :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

gFoldMapSumConsByte :: forall (p :: k10). (Word8 -> GenericFoldMapM m) -> C1 c f p -> GenericFoldMapM m Source #

GFoldMapSumConsByte tag f => GFoldMapSumConsByte (tag :: k1) (D1 c f :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

gFoldMapSumConsByte :: forall (p :: k10). (Word8 -> GenericFoldMapM tag) -> D1 c f p -> GenericFoldMapM tag Source #