bytezap-1.3.0: Bytestring builder with zero intermediate allocation
Safe HaskellSafe-Inferred
LanguageGHC2021

Bytezap.Struct.Generic

Description

Generics for bytezap's struct serializer.

We can't use my generic-data-functions library, because we're doing more than just basic monoidal composition. But I still want the same pluggable generics, where the user provides the class to use for base cases. So I do that. However, unlike g-d-f, the class info can't be provided via the user-selected monoid, because you don't select that. Instead, we take a simple "index" type. It's pretty much the same idea, surprisingly. This way, we can provide a few sensible "versions" like in g-f-d, while primarily designing for DIY.

Synopsis

Documentation

class GPokeBase tag where Source #

Class for holding info on class to use for poking base cases.

The type is just used to map to class info. It is never instantiated. By packing KnownSizeOf into here, we don't need to enforce a type-level solution! Now it's up to you how you want to track your constant lengths.

We stay unboxed here because the internals are unboxed, just for convenience. Maybe this is bad, let me know.

Associated Types

type GPokeBaseSt tag Source #

The state token of our poker.

type GPokeBaseC tag a :: Constraint Source #

The type class that provides base case poking.

The type class should provide a function that looks like gPokeBase.

type GPokeBaseLenTF tag :: Type ~> Natural Source #

Methods

gPokeBase :: GPokeBaseC tag a => a -> Poke# (GPokeBaseSt tag) Source #

class GPoke tag f where Source #

Methods

gPoke :: f p -> Poke# (GPokeBaseSt tag) Source #

Instances

Instances details
GPoke (tag :: k1) (U1 :: k2 -> Type) Source #

Wow, look! Nothing!

Instance details

Defined in Bytezap.Struct.Generic

Methods

gPoke :: forall (p :: k10). U1 p -> Poke# (GPokeBaseSt tag) Source #

(GPoke tag l, GPoke tag r, GPokeBase tag, lenL ~ GTFoldMapCAddition (GPokeBaseLenTF tag) l, KnownNat lenL) => GPoke (tag :: k1) (l :*: r :: k2 -> Type) Source # 
Instance details

Defined in Bytezap.Struct.Generic

Methods

gPoke :: forall (p :: k10). (l :*: r) p -> Poke# (GPokeBaseSt tag) Source #

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

Defined in Bytezap.Struct.Generic

Methods

gPoke :: forall (p :: k10). C1 c f p -> Poke# (GPokeBaseSt tag) Source #

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

Defined in Bytezap.Struct.Generic

Methods

gPoke :: forall (p :: k10). D1 c f p -> Poke# (GPokeBaseSt tag) Source #

(GPokeBase tag, GPokeBaseC tag a) => GPoke (tag :: k1) (S1 c (Rec0 a) :: k2 -> Type) Source # 
Instance details

Defined in Bytezap.Struct.Generic

Methods

gPoke :: forall (p :: k10). S1 c (Rec0 a) p -> Poke# (GPokeBaseSt tag) Source #