Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Symparsec.Parser.While
Synopsis
- type family While chPred p where ...
- type While' chPred pCh pEnd s0 = 'PParser (WhileChSym chPred pCh pEnd) pEnd s0
- sWhile :: Lam SChar SBool chPred -> SParser ss sr ('PParser pCh pEnd s0) -> SParser ss sr (While' chPred pCh pEnd s0)
- type WhileCh chPred pCh pEnd ch s = WhileCh' pCh pEnd ch s (chPred @@ ch)
- type family WhileCh' pCh pEnd ch s res where ...
- type family WhileCh'' res where ...
- type EWhile e = EIn "While" e
- eWhile :: SE e -> SE (EWhile e)
- data WhileChSym chPred pCh pEnd f
- data WhileChSym1 chPred pCh pEnd ch s
- sWhileChSym :: Lam SChar SBool chPred -> SParserChSym ss sr pCh -> SParserEndSym ss sr pEnd -> SParserChSym ss sr (WhileChSym chPred pCh pEnd)
Documentation
type family While chPred p where ... Source #
Run the given parser while the given character predicate succeeds.
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 #
data WhileChSym chPred pCh pEnd f Source #
Instances
(p ~ 'PParser pCh pEnd s0, SingParser p, SingChPred chPred) => SingParser (While' chPred pCh pEnd s0 :: PParser s r) Source # | |
type PR (While' chPred pCh pEnd s0 :: PParser s r) Source # | |
type PS (While' chPred pCh pEnd s0 :: PParser s r) Source # | |
type App (WhileChSym chPred pCh pEnd :: FunKind Char (s ~> PResult s r) -> Type) (f :: Char) Source # | |
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
type App (WhileChSym1 chPred pCh pEnd ch :: FunKind s1 (PResult s1 r) -> Type) (s2 :: s1) Source # | |
Defined in Symparsec.Parser.While |
sWhileChSym :: Lam SChar SBool chPred -> SParserChSym ss sr pCh -> SParserEndSym ss sr pEnd -> SParserChSym ss sr (WhileChSym chPred pCh pEnd) Source #