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

Symparsec.Parser.While

Synopsis

Documentation

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 While' chPred pCh pEnd s0 = 'PParser (WhileChSym chPred pCh pEnd) pEnd s0 Source #

sWhile :: Lam SChar SBool chPred -> SParser ss sr ('PParser pCh pEnd s0) -> SParser ss sr (While' chPred pCh pEnd s0) Source #

type WhileCh chPred pCh pEnd ch s = WhileCh' pCh pEnd ch s (chPred @@ ch) Source #

type family WhileCh' pCh pEnd ch s res where ... Source #

Equations

WhileCh' pCh pEnd ch s True = (pCh @@ ch) @@ s 
WhileCh' pCh pEnd ch s False = WhileCh'' (pEnd @@ s) 

type family WhileCh'' res where ... Source #

Equations

WhileCh'' (Right r) = Done r 
WhileCh'' (Left e) = Err (EWhile e) 

type EWhile e = EIn "While" e Source #

eWhile :: SE e -> SE (EWhile e) Source #

data WhileChSym chPred pCh pEnd f Source #

Instances

Instances details
(p ~ 'PParser pCh pEnd s0, SingParser p, SingChPred chPred) => SingParser (While' chPred pCh pEnd s0 :: PParser s r) Source # 
Instance details

Defined in Symparsec.Parser.While

Associated Types

type PS (While' chPred pCh pEnd s0) :: s -> Type Source #

type PR (While' chPred pCh pEnd s0) :: r -> Type Source #

Methods

singParser' :: SParser (PS (While' chPred pCh pEnd s0)) (PR (While' chPred pCh pEnd s0)) (While' chPred pCh pEnd s0) Source #

type PR (While' chPred pCh pEnd s0 :: PParser s r) Source # 
Instance details

Defined in Symparsec.Parser.While

type PR (While' chPred pCh pEnd s0 :: PParser s r) = PR ('PParser pCh pEnd s0)
type PS (While' chPred pCh pEnd s0 :: PParser s r) Source # 
Instance details

Defined in Symparsec.Parser.While

type PS (While' chPred pCh pEnd s0 :: PParser s r) = PS ('PParser pCh pEnd s0)
type App (WhileChSym chPred pCh pEnd :: FunKind Char (s ~> PResult s r) -> Type) (f :: Char) Source # 
Instance details

Defined in Symparsec.Parser.While

type App (WhileChSym chPred pCh pEnd :: FunKind Char (s ~> PResult s r) -> Type) (f :: Char) = WhileChSym1 chPred pCh pEnd f

data WhileChSym1 chPred pCh pEnd ch s Source #

Instances

Instances details
type App (WhileChSym1 chPred pCh pEnd ch :: FunKind s1 (PResult s1 r) -> Type) (s2 :: s1) Source # 
Instance details

Defined in Symparsec.Parser.While

type App (WhileChSym1 chPred pCh pEnd ch :: FunKind s1 (PResult s1 r) -> Type) (s2 :: s1) = WhileCh chPred pCh pEnd ch s2

sWhileChSym :: Lam SChar SBool chPred -> SParserChSym ss sr pCh -> SParserEndSym ss sr pEnd -> SParserChSym ss sr (WhileChSym chPred pCh pEnd) Source #