symparsec-1.1.1: Type level string parser combinators
Safe HaskellSafe-Inferred
LanguageGHC2021

Symparsec.Parsers

Description

Type-level string parsers.

You may ignore the equations that Haddock displays: they are internal and irrelevant to library usage.

Synopsis

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.

Equations

('PParser plCh plEnd s0l) :<*>: ('PParser prCh prEnd s0r) = Then' plCh plEnd s0l prCh prEnd s0r 

type family pl :*>: pr where ... infixl 4 Source #

Sequence two parsers, running left then right, and discard the return value of the left parser.

Equations

('PParser plCh plEnd s0l) :*>: ('PParser prCh prEnd s0r) = ThenVL' plCh plEnd s0l prCh prEnd s0r 

type family pl :<*: pr where ... infixl 4 Source #

Sequence two parsers, running left then right, and discard the return value of the right parser.

Equations

('PParser plCh plEnd s0l) :<*: ('PParser prCh prEnd s0r) = ThenVR' plCh plEnd s0l prCh prEnd s0r 

type family pl :<|>: pr where ... infixl 3 Source #

Limited parser choice. Try left; if it fails, backtrack and try right. However, _the right choice must consume at least as much as the left choice._ If it doesn't, then even if the right parser succeeds, it will emit an error.

This behaviour is due to the parser runner not supporting backtracking. We can emulate it by storing a record of the characters parsed so far, and "replaying" these on the right parser if the left parser fails. If the right parser ends before we finish replaying, we will have consumed extra characters that we can't ask the runner to revert.

For example, Literal "abcd" :|: Literal "ab" is bad. An input of abcX will trigger the consumption error.

I can't think of another way to implement this with the current parser design. I think it's the best we have. A more complex parser design may permit changing internal running state, so we could save and load state (this would permit a Try p parser). But that's scary. And you're better off designing your type-level string schemas to permit non-backtracking parsing anyway...

Also problematic is that we never emit a left parser error, so errors can degrade. Perhaps your string was one character off a successful left parse; but if it fails, you won't see that error.

Equations

('PParser plCh plEnd s0l) :<|>: ('PParser prCh prEnd s0r) = Or' plCh plEnd s0l prCh prEnd s0r 

Positional

Parsers that relate to symbol position e.g. length, end of symbol.

type Take n = 'PParser TakeChSym TakeEndSym '(n, '[]) Source #

Return the next n characters.

type TakeRest = 'PParser TakeRestChSym TakeRestEndSym '[] Source #

Return the remaining input string.

type Skip n = 'PParser SkipChSym SkipEndSym n Source #

Skip forward n characters. Fails if fewer than n characters are available'.

type End = 'PParser EndChSym (Con1 Right) '() 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 n ('PParser pCh pEnd s0) = Isolate' n pCh pEnd s0 

Predicated

Parsers that include character predicates.

type family While chPred p where ... Source #

Run the given parser while the given character predicate succeeds.

Equations

While chPred ('PParser pCh pEnd s0) = While' chPred pCh pEnd s0 

type TakeWhile chPred = While chPred TakeRest Source #

TODO unsorted

type family Count n p where ... Source #

Equations

Count n ('PParser pCh pEnd s0) = Count' n pCh pEnd s0 

Basic

Simple non-combinator parsers. Probably fundamental in some way e.g. very general or common.

type Literal str = 'PParser LiteralChSym LiteralEndSym str Source #

Parse the given Symbol.

Naturals

type NatDec = NatBase 10 ParseDigitDecSym Source #

Parse a decimal (base 10) natural.

type NatHex = NatBase 16 ParseDigitHexSym Source #

Parse a hexadecimal (base 16) natural. Permits mixed-case (0-9A-Fa-f).

type NatBin = NatBase 2 ParseDigitBinSym Source #

Parse a binary (base 2) natural.

type NatOct = NatBase 8 ParseDigitOctSym Source #

Parse an octal (base 8) natural.

type NatBase base parseDigit = 'PParser (NatBaseChSym base parseDigit) NatBaseEndSym Nothing Source #

Parse a natural in the given base, using the given digit parser.