Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Symparsec.Parser.Then
Synopsis
- type SPThen ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r = SParser (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (Then' plCh plEnd s0l prCh prEnd s0r)
- sThen :: SParser ssl srl ('PParser plCh plEnd s0l) -> SParser ssr srr ('PParser prCh prEnd s0r) -> SPThen ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r
- type family pl :<*>: pr where ...
- type Then' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenChSym plCh prCh s0r) (ThenEndSym plEnd prEnd s0r) (Left s0l)
- type family ThenCh plCh prCh s0r ch s where ...
- type family ThenChL prCh s0r ch resl where ...
- type EThenChL el = EIn "Then(L)" el
- eThenChL :: SE el -> SE (EThenChL el)
- type family ThenChR rl resr where ...
- type EThenChR er = EIn "Then(R)" er
- eThenChR :: SE er -> SE (EThenChR er)
- sThenChR :: srl rl -> SResult ssr srr resr -> SResult (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (ThenChR rl resr)
- sThenChSym :: SParserChSym ssl srl plCh -> SParserChSym ssr srr prCh -> ssr sr -> SParserChSym (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (ThenChSym plCh prCh sr)
- data ThenChSym plCh prCh s0r f
- data ThenChSym1 plCh prCh s0r ch s
- type family ThenEnd plEnd prEnd s0r s where ...
- type family ThenEndR rl res where ...
- type EThenEndR er = EIn "Then(R) end" er
- eThenEndR :: SE er -> SE (EThenEndR er)
- sThenEndR :: srl rl -> SResultEnd srr res -> SResultEnd (STuple2 srl srr) (ThenEndR rl res)
- type family ThenEndL prEnd s0r res where ...
- type EThenEndL er = EIn "Then(L) end" er
- eThenEndL :: SE er -> SE (EThenEndL er)
- sThenEndSym :: SParserEndSym ssl srl plEnd -> SParserEndSym ssr srr prEnd -> ssr s0r -> SParserEndSym (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (ThenEndSym plEnd prEnd s0r)
- data ThenEndSym plEnd prEnd s0r s
Documentation
type SPThen ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r = SParser (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (Then' plCh plEnd s0l prCh prEnd s0r) Source #
sThen :: SParser ssl srl ('PParser plCh plEnd s0l) -> SParser ssr srr ('PParser prCh prEnd s0r) -> SPThen ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r Source #
type family pl :<*>: pr where ... infixl 4 Source #
Sequence two parsers, running left then right, and return both results.
type Then' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenChSym plCh prCh s0r) (ThenEndSym plEnd prEnd s0r) (Left s0l) Source #
sThenChR :: srl rl -> SResult ssr srr resr -> SResult (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (ThenChR rl resr) Source #
sThenChSym :: SParserChSym ssl srl plCh -> SParserChSym ssr srr prCh -> ssr sr -> SParserChSym (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (ThenChSym plCh prCh sr) Source #
data ThenChSym plCh prCh s0r f Source #
Instances
(pl ~ 'PParser plCh plEnd s0l, pr ~ 'PParser prCh prEnd s0r, SingParser pl, SingParser pr) => SingParser (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # | |
type App (ThenChSym plCh prCh s0r :: FunKind Char (Either sl (rl, sr) ~> PResult (Either sl (rl, sr)) (rl, rr)) -> Type) (f :: Char) Source # | |
type PR (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # | |
type PS (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # | |
data ThenChSym1 plCh prCh s0r ch s Source #
sThenEndR :: srl rl -> SResultEnd srr res -> SResultEnd (STuple2 srl srr) (ThenEndR rl res) Source #
sThenEndSym :: SParserEndSym ssl srl plEnd -> SParserEndSym ssr srr prEnd -> ssr s0r -> SParserEndSym (SEither ssl (STuple2 srl ssr)) (STuple2 srl srr) (ThenEndSym plEnd prEnd s0r) Source #
data ThenEndSym plEnd prEnd s0r s Source #
Instances
(pl ~ 'PParser plCh plEnd s0l, pr ~ 'PParser prCh prEnd s0r, SingParser pl, SingParser pr) => SingParser (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # | |
type App (ThenEndSym plEnd prEnd s0r :: FunKind (Either a1 (k1, a2)) (PResultEnd (k1, k2)) -> Type) (s :: Either a1 (k1, a2)) Source # | |
Defined in Symparsec.Parser.Then type App (ThenEndSym plEnd prEnd s0r :: FunKind (Either a1 (k1, a2)) (PResultEnd (k1, k2)) -> Type) (s :: Either a1 (k1, a2)) = ThenEnd plEnd prEnd s0r s | |
type PR (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # | |
type PS (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # | |