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

Symparsec.Parser.Then.VoidLeft

Synopsis

Documentation

type SPThenVL ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r = SParser (SEither ssl ssr) srr (ThenVL' plCh plEnd s0l prCh prEnd s0r) Source #

sThenVL :: SParser ssl srl ('PParser plCh plEnd s0l) -> SParser ssr srr ('PParser prCh prEnd s0r) -> SPThenVL 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 left parser.

Equations

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

type ThenVL' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenVLChSym plCh prCh s0r) (ThenVLEndSym plEnd prEnd s0r) (Left s0l) Source #

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

Equations

ThenVLCh plCh prCh s0r ch (Left sl) = ThenVLChL prCh s0r ch ((plCh @@ ch) @@ sl) 
ThenVLCh plCh prCh s0r ch (Right sr) = ThenVLChR ((prCh @@ ch) @@ sr) 

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

Equations

ThenVLChL prCh s0r ch (Cont sl) = Cont (Left sl) 
ThenVLChL prCh s0r ch (Done rl) = ThenVLChR ((prCh @@ ch) @@ s0r) 
ThenVLChL prCh s0r ch (Err el) = Err (EThenVLChL el) 

type EThenVLChL el = EIn "ThenVL(L)" el Source #

type family ThenVLChR resr where ... Source #

Equations

ThenVLChR (Cont sr) = Cont (Right sr) 
ThenVLChR (Done rr) = Done rr 
ThenVLChR (Err er) = Err (EThenVLChR er) 

type EThenVLChR er = EIn "ThenVL(R)" er Source #

sThenVLChR :: SResult ssr srr resr -> SResult (SEither ssl ssr) srr (ThenVLChR resr) Source #

sThenVLChSym :: SParserChSym ssl srl plCh -> SParserChSym ssr srr prCh -> ssr sr -> SParserChSym (SEither ssl ssr) srr (ThenVLChSym plCh prCh sr) Source #

data ThenVLChSym plCh prCh sr f Source #

Instances

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

Defined in Symparsec.Parser.Then.VoidLeft

Associated Types

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

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

Methods

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

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

Defined in Symparsec.Parser.Then.VoidLeft

type App (ThenVLChSym plCh prCh s0r :: FunKind Char (Either sl sr ~> PResult (Either sl sr) rr) -> Type) (f :: Char) = ThenVLChSym1 plCh prCh s0r f
type PS (ThenVL' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl sr) r) Source # 
Instance details

Defined in Symparsec.Parser.Then.VoidLeft

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

Defined in Symparsec.Parser.Then.VoidLeft

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

data ThenVLChSym1 plCh prCh s0r ch s Source #

Instances

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

Defined in Symparsec.Parser.Then.VoidLeft

type App (ThenVLChSym1 plCh prCh s0r ch :: FunKind (Either sl sr) (PResult (Either sl sr) rr) -> Type) (s :: Either sl sr) = ThenVLCh plCh prCh s0r ch s

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

Equations

ThenVLEnd plEnd prEnd s0r (Right sr) = ThenVLEndR (prEnd @@ sr) 
ThenVLEnd plEnd prEnd s0r (Left sl) = ThenVLEndL prEnd s0r (plEnd @@ sl) 

type family ThenVLEndR res where ... Source #

Equations

ThenVLEndR (Right rr) = Right rr 
ThenVLEndR (Left er) = Left (EThenVLEndR er) 

type EThenVLEndR er = EIn "ThenVL(R) end" er Source #

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

Equations

ThenVLEndL prEnd s0r (Right rl) = ThenVLEndR (prEnd @@ s0r) 
ThenVLEndL prEnd s0r (Left el) = Left (EThenVLEndL el) 

type EThenVLEndL er = EIn "ThenVL(L) end" er Source #

sThenVLEndSym :: SParserEndSym ssl srl plEnd -> SParserEndSym ssr srr prEnd -> ssr s0r -> SParserEndSym (SEither ssl ssr) srr (ThenVLEndSym plEnd prEnd s0r) Source #

data ThenVLEndSym plEnd prEnd s0r s Source #

Instances

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

Defined in Symparsec.Parser.Then.VoidLeft

Associated Types

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

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

Methods

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

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

Defined in Symparsec.Parser.Then.VoidLeft

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

Defined in Symparsec.Parser.Then.VoidLeft

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

Defined in Symparsec.Parser.Then.VoidLeft

type App (ThenVLEndSym plEnd prEnd s0r :: FunKind (Either a1 a2) (PResultEnd b2) -> Type) (s :: Either a1 a2) = ThenVLEnd plEnd prEnd s0r s