Safe Haskell | None |
---|---|
Language | GHC2021 |
Bytezap.Parser.Struct.Generic
Documentation
class GParseBase (tag :: k) where Source #
Associated Types
type GParseBaseSt (tag :: k) :: ZeroBitType Source #
The state token of the parser.
type GParseBaseC (tag :: k) a Source #
type GParseBaseE (tag :: k) Source #
Methods
Arguments
:: GParseBaseC tag a | |
=> String | data type name |
-> String | constructor name |
-> Maybe String | record name (if present) |
-> Natural | field index |
-> ParserT (GParseBaseSt tag) (GParseBaseE tag) a |
class GParse (tag :: k) (gf :: k1 -> Type) where Source #
Methods
gParse :: forall (p :: k1). ParserT (GParseBaseSt tag) (GParseBaseE tag) (gf p) Source #
Instances
GParseC tag dtName cstrName 0 gf => GParse (tag :: k1) (D1 ('MetaData dtName _md2 _md3 _md4) (C1 ('MetaCons cstrName _mc2 _mc3) gf) :: k2 -> Type) Source # | |
Defined in Bytezap.Parser.Struct.Generic Methods gParse :: forall (p :: k2). ParserT (GParseBaseSt tag) (GParseBaseE tag) (D1 ('MetaData dtName _md2 _md3 _md4) (C1 ('MetaCons cstrName _mc2 _mc3) gf) p) Source # |
class GParseC (tag :: k) (cd :: Symbol) (cc :: Symbol) (si :: Natural) (gf :: k1 -> Type) where Source #
Methods
gParseC :: forall (p :: k1). ParserT (GParseBaseSt tag) (GParseBaseE tag) (gf p) Source #
Instances
GParseC (tag :: k1) cd cc 0 (U1 :: k2 -> Type) Source # | Wow, look! Nothing! |
Defined in Bytezap.Parser.Struct.Generic Methods gParseC :: forall (p :: k2). ParserT (GParseBaseSt tag) (GParseBaseE tag) (U1 p) Source # | |
(GParseC tag cd cc si l, GParseC tag cd cc (si + ProdArity r) r, GParseBase tag, lenL ~ GTFoldMapCAddition (GParseBaseLenTF tag) l, KnownNat lenL) => GParseC (tag :: k) cd cc si (l :*: r :: Type -> Type) Source # | |
Defined in Bytezap.Parser.Struct.Generic Methods gParseC :: ParserT (GParseBaseSt tag) (GParseBaseE tag) ((l :*: r) p) Source # | |
(GParseBase tag, GParseBaseC tag a, KnownNat si, ReifyMaybeSymbol mSelName, KnownSymbol cc, KnownSymbol cd) => GParseC (tag :: k1) cd cc si (S1 ('MetaSel mSelName _ms2 _ms3 _ms4) (Rec0 a) :: k2 -> Type) Source # | |
Defined in Bytezap.Parser.Struct.Generic Methods gParseC :: forall (p :: k2). ParserT (GParseBaseSt tag) (GParseBaseE tag) (S1 ('MetaSel mSelName _ms2 _ms3 _ms4) (Rec0 a) p) Source # |
class ReifyMaybeSymbol (mstr :: Maybe Symbol) where Source #
Methods
Instances
ReifyMaybeSymbol ('Nothing :: Maybe Symbol) Source # | |
Defined in Bytezap.Parser.Struct.Generic Methods | |
KnownSymbol str => ReifyMaybeSymbol ('Just str) Source # | |
Defined in Bytezap.Parser.Struct.Generic Methods |
symbolVal'' :: forall (sym :: Symbol). KnownSymbol sym => String Source #