Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Data.Type.Symbol.Parser
Synopsis
- type Parser s r = (ParserChSym s r, ParserEndSym s r, s)
- type family RunParser p sym where ...
- type family Isolate n p where ...
- type (:<*>:) pl pr = Then pl pr
- type (:*>:) pl pr = ThenVL pl pr
- type (:<*:) pl pr = ThenVR pl pr
- type Drop n = '(DropChSym, DropEndSym, n)
- type Literal sym = '(LiteralChSym, LiteralEndSym, UnconsSymbol sym)
- type End = '(EndChSym, EndEndSym, '())
- type NatDec = NatBase 10 ParseDecimalDigitSym
- type NatHex = NatBase 16 ParseHexDigitSym
- type NatBin = NatBase 2 ParseBinaryDigitSym
- type NatOct = NatBase 8 ParseOctalDigitSym
- type NatBase base parseDigit = '(NatBaseChSym base parseDigit, NatBaseEndSym, 0)
Base definitions
type Parser s r = (ParserChSym s r, ParserEndSym s r, s) Source #
type family RunParser p sym where ... Source #
Equations
RunParser '(pCh, pEnd, s) sym = RunParser' pCh pEnd 0 s (UnconsSymbol sym) |
Parsers
Combinators
type family Isolate n p where ... Source #
Equations
Isolate n '(pCh, pEnd, s) = '(IsolateChSym pCh pEnd, IsolateEndSym, '(n, s)) |
type (:*>:) pl pr = ThenVL pl pr Source #
Sequence parsers, discarding the return value of the left parser
type (:<*:) pl pr = ThenVR pl pr Source #
Sequence parsers, discarding the return value of the right parser.
Consider using :*>:
instead, which is simpler and potentially faster since
we parse L->R.
Primitives
type Literal sym = '(LiteralChSym, LiteralEndSym, UnconsSymbol sym) Source #
Naturals
type NatDec = NatBase 10 ParseDecimalDigitSym Source #
type NatHex = NatBase 16 ParseHexDigitSym Source #
type NatBin = NatBase 2 ParseBinaryDigitSym Source #
type NatOct = NatBase 8 ParseOctalDigitSym Source #
type NatBase base parseDigit = '(NatBaseChSym base parseDigit, NatBaseEndSym, 0) Source #