symbol-parser-0.3.0: Type level string parser combinators
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Type.Symbol.Parser

Synopsis

Base definitions

type Parser s r = (ParserChSym s r, ParserEndSym s r, s) Source #

A parser you can pass (heh) around.

Parsers are defined by the product of a ParserCh character parser, ParserEnd end handler, and s starting state.

type family Run p sym where ... Source #

Run the given parser on the given Symbol.

Equations

Run '(pCh, pEnd, s) sym = MapLeftPrettyERun (RunStart pCh pEnd s (UnconsSymbol sym)) 

Parsers

Combinators

type family Isolate n p where ... Source #

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)) 

type (:<*>:) pl pr = Then pl pr Source #

Sequence parsers, returning both values in a tuple.

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.

type (:<|>:) pl pr = Or pl pr Source #

Primitives

type family Take n where ... Source #

Equations

Take 0 = '(FailChSym "Take" (ErrParserLimitation "can't take 0"), TakeEndSym, '(0, '[])) 
Take n = '(TakeChSym, TakeEndSym, '(n, '[])) 

type family Drop n where ... Source #

Equations

Drop 0 = '(FailChSym "Drop" (ErrParserLimitation "can't drop 0"), DropEndSym, 0) 
Drop n = Drop' n 

type Literal sym = Literal' (UnconsSymbol sym) Source #

type End = '(EndChSym, EmitEndSym, '()) 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, EmitEndSym, 0) Source #