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

Symparsec.Parser.Then

Synopsis

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.

Equations

('PParser plCh plEnd s0l) :<*>: ('PParser prCh prEnd s0r) = Then' plCh plEnd s0l prCh prEnd s0r 

type Then' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenChSym plCh prCh s0r) (ThenEndSym plEnd prEnd s0r) (Left s0l) Source #

type family ThenCh plCh prCh s0r ch s where ... Source #

Equations

ThenCh plCh prCh s0r ch (Left sl) = ThenChL prCh s0r ch ((plCh @@ ch) @@ sl) 
ThenCh plCh prCh s0r ch (Right '(rl, sr)) = ThenChR rl ((prCh @@ ch) @@ sr) 

type family ThenChL prCh s0r ch resl where ... Source #

Equations

ThenChL prCh s0r ch (Cont sl) = Cont (Left sl) 
ThenChL prCh s0r ch (Done rl) = ThenChR rl ((prCh @@ ch) @@ s0r) 
ThenChL prCh s0r ch (Err el) = Err (EThenChL el) 

type EThenChL el = EIn "Then(L)" el Source #

eThenChL :: SE el -> SE (EThenChL el) Source #

type family ThenChR rl resr where ... Source #

Equations

ThenChR rl (Cont sr) = Cont (Right '(rl, sr)) 
ThenChR rl (Done rr) = Done '(rl, rr) 
ThenChR rl (Err er) = Err (EThenChR er) 

type EThenChR er = EIn "Then(R)" er Source #

eThenChR :: SE er -> SE (EThenChR er) 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

Instances details
(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 # 
Instance details

Defined in Symparsec.Parser.Then

Associated Types

type PS (Then' plCh plEnd s0l prCh prEnd s0r) :: s -> Type Source #

type PR (Then' plCh plEnd s0l prCh prEnd s0r) :: r -> Type Source #

Methods

singParser' :: SParser (PS (Then' plCh plEnd s0l prCh prEnd s0r)) (PR (Then' plCh plEnd s0l prCh prEnd s0r)) (Then' plCh plEnd s0l prCh prEnd s0r) Source #

type App (ThenChSym plCh prCh s0r :: FunKind Char (Either sl (rl, sr) ~> PResult (Either sl (rl, sr)) (rl, rr)) -> Type) (f :: Char) Source # 
Instance details

Defined in Symparsec.Parser.Then

type App (ThenChSym plCh prCh s0r :: FunKind Char (Either sl (rl, sr) ~> PResult (Either sl (rl, sr)) (rl, rr)) -> Type) (f :: Char) = ThenChSym1 plCh prCh s0r f
type PR (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # 
Instance details

Defined in Symparsec.Parser.Then

type PR (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) = STuple2 (PR ('PParser plCh plEnd s0l)) (PR ('PParser prCh prEnd s0r))
type PS (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # 
Instance details

Defined in Symparsec.Parser.Then

type PS (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) = SEither (PS ('PParser plCh plEnd s0l)) (STuple2 (PR ('PParser plCh plEnd s0l)) (PS ('PParser prCh prEnd s0r)))

data ThenChSym1 plCh prCh s0r ch s Source #

Instances

Instances details
type App (ThenChSym1 plCh prCh s0r ch :: FunKind (Either sl (rl, sr)) (PResult (Either sl (rl, sr)) (rl, rr)) -> Type) (s :: Either sl (rl, sr)) Source # 
Instance details

Defined in Symparsec.Parser.Then

type App (ThenChSym1 plCh prCh s0r ch :: FunKind (Either sl (rl, sr)) (PResult (Either sl (rl, sr)) (rl, rr)) -> Type) (s :: Either sl (rl, sr)) = ThenCh plCh prCh s0r ch s

type family ThenEnd plEnd prEnd s0r s where ... Source #

Equations

ThenEnd plEnd prEnd s0r (Right '(rl, sr)) = ThenEndR rl (prEnd @@ sr) 
ThenEnd plEnd prEnd s0r (Left sl) = ThenEndL prEnd s0r (plEnd @@ sl) 

type family ThenEndR rl res where ... Source #

Equations

ThenEndR rl (Right rr) = Right '(rl, rr) 
ThenEndR rl (Left er) = Left (EThenEndR er) 

type EThenEndR er = EIn "Then(R) end" er Source #

sThenEndR :: srl rl -> SResultEnd srr res -> SResultEnd (STuple2 srl srr) (ThenEndR rl res) Source #

type family ThenEndL prEnd s0r res where ... Source #

Equations

ThenEndL prEnd s0r (Right rl) = ThenEndR rl (prEnd @@ s0r) 
ThenEndL prEnd s0r (Left el) = Left (EThenEndL el) 

type EThenEndL er = EIn "Then(L) end" er 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

Instances details
(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 # 
Instance details

Defined in Symparsec.Parser.Then

Associated Types

type PS (Then' plCh plEnd s0l prCh prEnd s0r) :: s -> Type Source #

type PR (Then' plCh plEnd s0l prCh prEnd s0r) :: r -> Type Source #

Methods

singParser' :: SParser (PS (Then' plCh plEnd s0l prCh prEnd s0r)) (PR (Then' plCh plEnd s0l prCh prEnd s0r)) (Then' plCh plEnd s0l prCh prEnd s0r) Source #

type App (ThenEndSym plEnd prEnd s0r :: FunKind (Either a1 (k1, a2)) (PResultEnd (k1, k2)) -> Type) (s :: Either a1 (k1, a2)) Source # 
Instance details

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 # 
Instance details

Defined in Symparsec.Parser.Then

type PR (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) = STuple2 (PR ('PParser plCh plEnd s0l)) (PR ('PParser prCh prEnd s0r))
type PS (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) Source # 
Instance details

Defined in Symparsec.Parser.Then

type PS (Then' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (rl, sr)) (rl, rr)) = SEither (PS ('PParser plCh plEnd s0l)) (STuple2 (PR ('PParser plCh plEnd s0l)) (PS ('PParser prCh prEnd s0r)))