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

Symparsec.Parser.Then.VoidRight

Synopsis

Documentation

type SPThenVR ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r = SParser (SEither ssl (STuple2 srl ssr)) srl (ThenVR' plCh plEnd s0l prCh prEnd s0r) Source #

sThenVR :: SParser ssl srl ('PParser plCh plEnd s0l) -> SParser ssr srr ('PParser prCh prEnd s0r) -> SPThenVR 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 discard the return value of the right parser.

Equations

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

type ThenVR' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenVRChSym plCh prCh s0r) (ThenVREndSym plEnd prEnd s0r) (Left s0l) Source #

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

Equations

ThenVRCh plCh prCh s0r ch (Left sl) = ThenVRChL prCh s0r ch ((plCh @@ ch) @@ sl) 
ThenVRCh plCh prCh s0r ch (Right '(rl, sr)) = ThenVRChR rl ((prCh @@ ch) @@ sr) 

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

Equations

ThenVRChL prCh s0r ch (Cont sl) = Cont (Left sl) 
ThenVRChL prCh s0r ch (Done rl) = ThenVRChR rl ((prCh @@ ch) @@ s0r) 
ThenVRChL prCh s0r ch (Err el) = Err (EThenVRChL el) 

type EThenVRChL el = EIn "ThenVR(L)" el Source #

type family ThenVRChR rl resr where ... Source #

Equations

ThenVRChR rl (Cont sr) = Cont (Right '(rl, sr)) 
ThenVRChR rl (Done rr) = Done rl 
ThenVRChR rl (Err er) = Err (EThenVRChR er) 

type EThenVRChR er = EIn "ThenVR(R)" er Source #

sThenVRChR :: srl rl -> SResult ssr srr resr -> SResult (SEither ssl (STuple2 srl ssr)) srl (ThenVRChR rl resr) Source #

sThenVRChSym :: SParserChSym ssl srl plCh -> SParserChSym ssr srr prCh -> ssr sr -> SParserChSym (SEither ssl (STuple2 srl ssr)) srl (ThenVRChSym plCh prCh sr) Source #

data ThenVRChSym plCh prCh s0r f Source #

Instances

Instances details
(pl ~ 'PParser plCh plEnd s0l, pr ~ 'PParser prCh prEnd s0r, SingParser pl, SingParser pr) => SingParser (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # 
Instance details

Defined in Symparsec.Parser.Then.VoidRight

Associated Types

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

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

Methods

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

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

Defined in Symparsec.Parser.Then.VoidRight

type App (ThenVRChSym plCh prCh s0r :: FunKind Char (Either sl (rl, sr) ~> PResult (Either sl (rl, sr)) rl) -> Type) (f :: Char) = ThenVRChSym1 plCh prCh s0r f
type PS (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # 
Instance details

Defined in Symparsec.Parser.Then.VoidRight

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

Defined in Symparsec.Parser.Then.VoidRight

type PR (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) = PR ('PParser plCh plEnd s0l)

data ThenVRChSym1 plCh prCh s0r ch s Source #

Instances

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

Defined in Symparsec.Parser.Then.VoidRight

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

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

Equations

ThenVREnd plEnd prEnd s0r (Right '(rl, sr)) = ThenVREndR rl (prEnd @@ sr) 
ThenVREnd plEnd prEnd s0r (Left sl) = ThenVREndL prEnd s0r (plEnd @@ sl) 

type family ThenVREndR rl res where ... Source #

Equations

ThenVREndR rl (Right rr) = Right rl 
ThenVREndR rl (Left er) = Left (EThenVREndR er) 

type EThenVREndR er = EIn "ThenVR(R) end" er Source #

sThenVREndR :: srl rl -> SResultEnd srr res -> SResultEnd srl (ThenVREndR rl res) Source #

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

Equations

ThenVREndL prEnd s0r (Right rl) = ThenVREndR rl (prEnd @@ s0r) 
ThenVREndL prEnd s0r (Left el) = Left (EThenVREndL el) 

type EThenVREndL er = EIn "ThenVR(L) end" er Source #

sThenVREndSym :: SParserEndSym ssl srl plEnd -> SParserEndSym ssr srr prEnd -> ssr s0r -> SParserEndSym (SEither ssl (STuple2 srl ssr)) srl (ThenVREndSym plEnd prEnd s0r) Source #

data ThenVREndSym plEnd prEnd s0r s Source #

Instances

Instances details
(pl ~ 'PParser plCh plEnd s0l, pr ~ 'PParser prCh prEnd s0r, SingParser pl, SingParser pr) => SingParser (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # 
Instance details

Defined in Symparsec.Parser.Then.VoidRight

Associated Types

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

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

Methods

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

type PS (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # 
Instance details

Defined in Symparsec.Parser.Then.VoidRight

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

Defined in Symparsec.Parser.Then.VoidRight

type PR (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) = PR ('PParser plCh plEnd s0l)
type App (ThenVREndSym plEnd prEnd s0r :: FunKind (Either a1 (b1, a2)) (PResultEnd b1) -> Type) (s :: Either a1 (b1, a2)) Source # 
Instance details

Defined in Symparsec.Parser.Then.VoidRight

type App (ThenVREndSym plEnd prEnd s0r :: FunKind (Either a1 (b1, a2)) (PResultEnd b1) -> Type) (s :: Either a1 (b1, a2)) = ThenVREnd plEnd prEnd s0r s