symparsec
Safe HaskellNone
LanguageGHC2021

Symparsec.Parsers

Description

Common type-level string parsers.

Many parsers reuse term-level names, which can cause ambiguity issues. Consider importing qualified.

Synopsis

Type class-esque

Parsers which mirror functions from type classes (specifically Functor, Applicative, Monad and Alternative. These primitive combinators are powerful, but can be tough to use without type-level binders or do-notation, and force interacting with defunctionalization.

data ((f :: a ~> b) <$> (p :: PParser a)) (s :: FunKind PState (PReply b)) infixl 4 Source #

<$> for parsers. Apply the given type function to the result.

Instances

Instances details
type App (f <$> p :: FunKind PState (PReply a2) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Functor

type App (f <$> p :: FunKind PState (PReply a2) -> Type) (s :: PState)

data ((l :: PParser (a ~> b)) <*> (r :: PParser a)) (s :: FunKind PState (PReply b)) infixl 4 Source #

<*> for parsers. Sequence two parsers, left to right.

Instances

Instances details
type App (l <*> r :: FunKind PState (PReply b) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Applicative

type App (l <*> r :: FunKind PState (PReply b) -> Type) (s :: PState)

data Pure (a1 :: a) (s :: FunKind PState (PReply a)) Source #

pure for parsers. Non-consuming parser that just returns the given value.

Instances

Instances details
type App (Pure a2 :: FunKind PState (PReply a1) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Applicative

type App (Pure a2 :: FunKind PState (PReply a1) -> Type) (s :: PState) = 'Reply ('OK a2 :: Result Symbol Natural a1) s

type LiftA2 (f :: a ~> (b ~> c)) (l :: PParser a) (r :: PParser b) = (f <$> l) <*> r Source #

liftA2 for parsers. Sequence two parsers, and combine their results with a binary type function.

type (*>) (l :: PParser a) (r :: PParser b) = ((IdSym :: FunKind b b -> Type) <$ l) <*> r infixl 4 Source #

*> for parsers. Sequence two parsers left to right, discarding the value of the left parser.

type (<*) (l :: PParser a) (r :: PParser b) = LiftA2 (ConstSym :: FunKind a (b ~> a) -> Type) l r infixl 4 Source #

<* for parsers. Sequence two parsers left to right, discarding the value of the right parser.

data ((l :: PParser a) >>= (r :: a ~> PParser b)) (s :: FunKind PState (PReply b)) infixl 1 Source #

>>= for parsers. Sequentially compose two parsers, passing the value from the left parser as an argument to the second.

Instances

Instances details
type App (l >>= r :: FunKind PState (PReply b) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Monad

type App (l >>= r :: FunKind PState (PReply b) -> Type) (s :: PState)

data ((l :: PParser a) <|> (r :: PParser a)) (s :: FunKind PState (PReply a)) infixl 3 Source #

<|> for parsers. Try the left parser; if it succeeds, return the result, else try the right parser with the left parser's output state.

Does not backtrack. Wrap parsers with Try as needed.

TODO shitty errors

Instances

Instances details
type App (l <|> r :: FunKind PState (PReply a) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Alternative

type App (l <|> r :: FunKind PState (PReply a) -> Type) (s :: PState)

data Empty (s :: FunKind PState (PReply a)) Source #

empty for parsers. Immediately fail with no consumption.

Instances

Instances details
type App (Empty :: FunKind PState (PReply a) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Alternative

type App (Empty :: FunKind PState (PReply a) -> Type) (s :: PState) = 'Reply ('Err (Error1 "called empty parser") :: Result Symbol Natural a) s

type Optional (p :: PParser a) = (Con1 ('Just :: a -> Maybe a) <$> p) <|> Pure ('Nothing :: Maybe a) Source #

optional for parsers.

Positional

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

data Ensure (n :: Natural) (s :: FunKind PState (PReply ())) Source #

Assert that there are at least n characters remaining. Non-consuming.

Instances

Instances details
type App (Ensure n :: FunKind PState (PReply ()) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Ensure

type App (Ensure n :: FunKind PState (PReply ()) -> Type) (s :: PState)

data Isolate (n :: Natural) (p :: PParser a) (s :: FunKind PState (PReply a)) Source #

Instances

Instances details
type App (Isolate n p :: FunKind PState (PReply a) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Isolate

type App (Isolate n p :: FunKind PState (PReply a) -> Type) (s :: PState)

data Take (n :: Natural) (s :: FunKind PState (PReply Symbol)) Source #

Return the next n characters.

Instances

Instances details
type App (Take n :: FunKind PState (PReply Symbol) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Take

type App (Take n :: FunKind PState (PReply Symbol) -> Type) (s :: PState)

data TakeRest (s :: FunKind PState (PReply Symbol)) Source #

Consume and return the rest of the input string.

Never fails. May return the empty string.

Instances

Instances details
type App TakeRest (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.TakeRest

type App TakeRest (s :: PState)

type Skip (n :: Natural) = Ensure n *> SkipUnsafe n Source #

Skip forward n characters. Fails if fewer than n characters remain.

data Eof (s :: FunKind PState (PReply ())) Source #

Assert end of input, or fail.

Instances

Instances details
type App Eof (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Eof

type App Eof (s :: PState)

Other combinators

Assorted parser combinators (that wrap other parsers).

data Try (p :: PParser a) (s :: FunKind PState (PReply a)) Source #

Run the given parser, backtracking on error.

Instances

Instances details
type App (Try p :: FunKind PState (PReply a) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Try

type App (Try p :: FunKind PState (PReply a) -> Type) (s :: PState)

data While (chPred :: Char ~> Bool) (p :: PParser a) (s :: FunKind PState (PReply a)) Source #

Run the given parser while the given character predicate succeeds.

Instances

Instances details
type App (While chPred p :: FunKind PState (PReply a) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.While

type App (While chPred p :: FunKind PState (PReply a) -> Type) (s :: PState)

data TakeWhile (chPred :: Char ~> Bool) (s :: FunKind PState (PReply Symbol)) Source #

Take zero or more Chars for which the supplied predicate holds.

May also be defined via While chPred TakeRest, but a custom implementation is more efficient.

Instances

Instances details
type App (TakeWhile chPred :: FunKind PState (PReply Symbol) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.TakeWhile

type App (TakeWhile chPred :: FunKind PState (PReply Symbol) -> Type) (s :: PState)

data Count (n :: Natural) (p :: PParser a) (s :: FunKind PState (PReply [a])) Source #

Count n p parses n occurrences of p.

Instances

Instances details
type App (Count n p :: FunKind PState (PReply [k]) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Count

type App (Count n p :: FunKind PState (PReply [k]) -> Type) (s :: PState)

Common non-combinator

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

data Literal (lit :: Symbol) (s :: FunKind PState (PReply ())) Source #

Instances

Instances details
type App (Literal lit :: FunKind PState (PReply ()) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Literal

type App (Literal lit :: FunKind PState (PReply ()) -> Type) (s :: PState)

Naturals

data NatBase (base :: Natural) (parseDigit :: Char ~> Maybe Natural) (s :: FunKind PState (PReply Natural)) Source #

Parse a non-empty Natural using the given base and digit parser.

Only permits parsing numbers with digits exactly one Char long.

Returns an error if it parses zero digits, or if any character fails to parse.

Instances

Instances details
type App (NatBase base parseDigit :: FunKind PState (PReply Natural) -> Type) (s :: PState) Source # 
Instance details

Defined in Symparsec.Parser.Natural

type App (NatBase base parseDigit :: FunKind PState (PReply Natural) -> Type) (s :: PState)

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.

Derived

Derived parsers. Should be type synonyms.

type Tuple (l :: PParser a) (r :: PParser b) = LiftA2 (Con2 ('(,) :: a -> b -> (a, b))) l r Source #

Parse left, then right, and return their results in a tuple.

Classic parser combinators often don't define this because it's trivial, and do notation is often cleaner anyway. But it's very syntactically busy on the type level, and we don't have do notation. So here's a convenience definition.

Missing parsers

Certain term-level parsers you may be used to you will not see in Symparsec:

  • Parsers that rely on underlying instances e.g. no Semigroup a => Semigroup (parser a) because we'd have to pass Semigroup a manually, which defeats the purpose