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

Generic.Data.Function.FoldMap.SumConsByte

Description

foldMap for sum types, where constructors are encoded by index (distance from first/leftmost constructor) in a single byte, which is prepended to their contents.

TODO. Clumsy and limited. And yet, still handy enough I think.

Synopsis

Documentation

class GFoldMapSumConsByte tag f where Source #

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 #

class GFoldMapCSumCtr tag f where Source #

Sum type handler handling constructors only. Useful if you handle constructor prefixes elsewhere.

Instances

Instances details
(GFoldMapCSumCtr tag l, GFoldMapCSumCtr tag r) => GFoldMapCSumCtr (tag :: k1) (l :+: r :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

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

GFoldMapC tag f => GFoldMapCSumCtr (tag :: k1) (C1 c f :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

gFoldMapCSumCtr :: forall (p :: k10). C1 c f p -> GenericFoldMapM tag Source #

class GFoldMapCSumCtrArityByte tag (arity :: Natural) f where Source #

Instances

Instances details
(GFoldMapCSumCtrArityByte tag arity l, GFoldMapCSumCtrArityByte tag (arity + SumArity l) r) => GFoldMapCSumCtrArityByte (tag :: k) arity (l :+: r :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

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

KnownNat arity => GFoldMapCSumCtrArityByte (tag :: k1) arity (C1 c f :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.FoldMap.SumConsByte

Methods

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

type family SumArity (a :: Type -> Type) :: Natural where ... Source #

Equations

SumArity (C1 c a) = 1 
SumArity (x :+: y) = SumArity x + SumArity y 

type family FitsInByteResult (b :: Bool) :: Constraint where ... Source #

Equations

FitsInByteResult 'True = () 
FitsInByteResult 'False = TypeErrorMessage "TODO ya type had more than 255 constructors" 

type family TypeErrorMessage (a :: Symbol) :: Constraint where ... Source #

Equations

TypeErrorMessage a = TypeError ('Text a)