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

Symparsec.Parser.Literal

Synopsis

Documentation

type Literal str = 'PParser LiteralChSym LiteralEndSym str Source #

Parse the given Symbol.

type LiteralCh ch str = LiteralCh' ch (UnconsSymbol str) Source #

type family LiteralCh' ch str where ... Source #

Equations

LiteralCh' ch (Just '(ch, str)) = Cont str 
LiteralCh' ch (Just '(chNext, str)) = Err (EWrongChar chNext ch) 
LiteralCh' ch Nothing = Done '() 

type EWrongChar chNext ch = EBase "Literal" (((Text "expected " :<>: Text (ShowChar chNext)) :<>: Text ", got ") :<>: Text (ShowChar ch)) Source #

eWrongChar :: SChar chNext -> SChar ch -> SE (EWrongChar chNext ch) Source #

data LiteralChSym f Source #

Instances

Instances details
KnownSymbol str => SingParser (Literal str :: PParser Symbol ()) Source # 
Instance details

Defined in Symparsec.Parser.Literal

Associated Types

type PS (Literal str) :: s -> Type Source #

type PR (Literal str) :: r -> Type Source #

Methods

singParser' :: SParser (PS (Literal str)) (PR (Literal str)) (Literal str) Source #

type PR (Literal str :: PParser Symbol ()) Source # 
Instance details

Defined in Symparsec.Parser.Literal

type PR (Literal str :: PParser Symbol ()) = SUnit
type PS (Literal str :: PParser Symbol ()) Source # 
Instance details

Defined in Symparsec.Parser.Literal

type PS (Literal str :: PParser Symbol ()) = SSymbol
type App LiteralChSym (f :: Char) Source # 
Instance details

Defined in Symparsec.Parser.Literal

data LiteralChSym1 ch s Source #

Instances

Instances details
type App (LiteralChSym1 ch :: FunKind Symbol (PResult Symbol ()) -> Type) (s :: Symbol) Source # 
Instance details

Defined in Symparsec.Parser.Literal

type App (LiteralChSym1 ch :: FunKind Symbol (PResult Symbol ()) -> Type) (s :: Symbol) = LiteralCh ch s

type family LiteralEnd str where ... Source #

Equations

LiteralEnd "" = Right '() 
LiteralEnd str = Left (EStillParsing str) 

type EStillParsing str = EBase "Literal" (Text "still parsing literal: " :<>: Text str) Source #

data LiteralEndSym s Source #

Instances

Instances details
KnownSymbol str => SingParser (Literal str :: PParser Symbol ()) Source # 
Instance details

Defined in Symparsec.Parser.Literal

Associated Types

type PS (Literal str) :: s -> Type Source #

type PR (Literal str) :: r -> Type Source #

Methods

singParser' :: SParser (PS (Literal str)) (PR (Literal str)) (Literal str) Source #

type PR (Literal str :: PParser Symbol ()) Source # 
Instance details

Defined in Symparsec.Parser.Literal

type PR (Literal str :: PParser Symbol ()) = SUnit
type PS (Literal str :: PParser Symbol ()) Source # 
Instance details

Defined in Symparsec.Parser.Literal

type PS (Literal str :: PParser Symbol ()) = SSymbol
type App LiteralEndSym (s :: Symbol) Source # 
Instance details

Defined in Symparsec.Parser.Literal