| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Symparsec.Parsers
Description
Re-exported type-level symbol parsers.
You may ignore the equations that Haddock displays: they are internal and irrelevant to library usage.
Synopsis
- type family pl :<*>: pr where ...
- type family pl :*>: pr where ...
- type family pl :<*: pr where ...
- type family pl :<|>: pr where ...
- type family Take n where ...
- type family Skip n where ...
- type End = '(FailChSym "End" (Text "expected end of symbol"), EmitEndSym, '())
- type family Isolate n p where ...
- type Literal sym = Literal' (UnconsSymbol sym)
- 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, EmitEndSym, 0)
Binary combinators
Parsers that combine two parsers. Any parsers that have term-level parallels
will use the same fixity e.g. :<*>: is infixl 4, same as <*>.
type family pl :<*>: pr where ... infixl 4 Source #
Sequence two parsers, running left then right, and return both results.
type family pl :*>: pr where ... infixl 4 Source #
Sequence two parsers, running left then right, and discard the return value of the left parser.
type family pl :<*: pr where ... infixl 4 Source #
Sequence two parsers, running left then right, and discard the return value of the right parser.
Consider using :*>: instead,
which is simpler and potentially faster since we parse left-to-right.
type family pl :<|>: pr where ... infixl 3 Source #
Parser choice. Try left; if it fails, backtrack and try right.
Be warned that this parser is experimental, and likely brittle. If possible, consider designing your schema to permit non-backtracking parsing. Or if not, have both sides always parse the same length, in which case this parser should probably work fine.
Positional
Parsers that relate to symbol position e.g. length, end of symbol.
type family Take n where ... Source #
Return the next n characters.
Equations
| Take 0 = '(FailChSym "Take" (ErrParserLimitation "can't take 0"), TakeEndSym, '(0, '[])) | |
| Take n = '(TakeChSym, TakeEndSym, '(n, '[])) |
type family Skip n where ... Source #
Skip forward n characters. Fails if fewer than n characters are
available.
Equations
| Skip 0 = '(FailChSym "Skip" (ErrParserLimitation "can't drop 0"), SkipEndSym, 0) | |
| Skip n = Skip' n |
type End = '(FailChSym "End" (Text "expected end of symbol"), EmitEndSym, '()) Source #
Assert end of symbol, or fail.
type family Isolate n p where ... Source #
Run the given parser isolated to the next n characters.
All isolated characters must be consumed.
Equations
| Isolate 0 '(pCh, pEnd, s) = '(FailChSym "Isolate" (ErrParserLimitation "cannot isolate 0"), IsolateEndSym, '(0, s)) | |
| Isolate n '(pCh, pEnd, s) = '(IsolateChSym pCh pEnd, IsolateEndSym, '(n - 1, s)) |
Basic
Simple non-combinator parsers. Probably fundamental in some way e.g. very general or common.
type Literal sym = Literal' (UnconsSymbol sym) Source #
Parse the given Symbol.
Naturals
type NatHex = NatBase 16 ParseHexDigitSym Source #
Parse a hexadecimal (base 16) natural. Permits mixed-case (0-9A-Fa-f).
type NatBase base parseDigit = '(NatBaseChSym base parseDigit, EmitEndSym, 0) Source #
Parse a natural in the given base, using the given digit parser.