Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- type SPThenVL ssl srl ssr srr plCh plEnd s0l prCh prEnd s0r = SParser (SEither ssl ssr) srr (ThenVL' plCh plEnd s0l prCh prEnd s0r)
- 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
- type family pl :*>: pr where ...
- type ThenVL' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenVLChSym plCh prCh s0r) (ThenVLEndSym plEnd prEnd s0r) (Left s0l)
- type family ThenVLCh plCh prCh s0r ch s where ...
- type family ThenVLChL prCh s0r ch resl where ...
- type EThenVLChL el = EIn "ThenVL(L)" el
- eThenVLChL :: SE el -> SE (EThenVLChL el)
- type family ThenVLChR resr where ...
- type EThenVLChR er = EIn "ThenVL(R)" er
- eThenVLChR :: SE er -> SE (EThenVLChR er)
- sThenVLChR :: SResult ssr srr resr -> SResult (SEither ssl ssr) srr (ThenVLChR resr)
- sThenVLChSym :: SParserChSym ssl srl plCh -> SParserChSym ssr srr prCh -> ssr sr -> SParserChSym (SEither ssl ssr) srr (ThenVLChSym plCh prCh sr)
- data ThenVLChSym plCh prCh sr f
- data ThenVLChSym1 plCh prCh s0r ch s
- type family ThenVLEnd plEnd prEnd s0r s where ...
- type family ThenVLEndR res where ...
- type EThenVLEndR er = EIn "ThenVL(R) end" er
- eThenVLEndR :: SE er -> SE (EThenVLEndR er)
- sThenVLEndR :: SResultEnd srr res -> SResultEnd srr (ThenVLEndR res)
- type family ThenVLEndL prEnd s0r res where ...
- type EThenVLEndL er = EIn "ThenVL(L) end" er
- eThenVLEndL :: SE er -> SE (EThenVLEndL er)
- sThenVLEndSym :: SParserEndSym ssl srl plEnd -> SParserEndSym ssr srr prEnd -> ssr s0r -> SParserEndSym (SEither ssl ssr) srr (ThenVLEndSym plEnd prEnd s0r)
- data ThenVLEndSym plEnd prEnd s0r s
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.
type ThenVL' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenVLChSym plCh prCh s0r) (ThenVLEndSym plEnd prEnd s0r) (Left s0l) Source #
type EThenVLChL el = EIn "ThenVL(L)" el Source #
eThenVLChL :: SE el -> SE (EThenVLChL el) Source #
type EThenVLChR er = EIn "ThenVL(R)" er Source #
eThenVLChR :: SE er -> SE (EThenVLChR er) 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
(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 # | |
type App (ThenVLChSym plCh prCh s0r :: FunKind Char (Either sl sr ~> PResult (Either sl sr) rr) -> Type) (f :: Char) Source # | |
Defined in Symparsec.Parser.Then.VoidLeft | |
type PS (ThenVL' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl sr) r) Source # | |
type PR (ThenVL' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl sr) r) Source # | |
data ThenVLChSym1 plCh prCh s0r ch s Source #
type family ThenVLEnd plEnd prEnd s0r s where ... Source #
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 #
ThenVLEndR (Right rr) = Right rr | |
ThenVLEndR (Left er) = Left (EThenVLEndR er) |
type EThenVLEndR er = EIn "ThenVL(R) end" er Source #
eThenVLEndR :: SE er -> SE (EThenVLEndR er) Source #
sThenVLEndR :: SResultEnd srr res -> SResultEnd srr (ThenVLEndR res) Source #
type family ThenVLEndL prEnd s0r res where ... Source #
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 #
eThenVLEndL :: SE er -> SE (EThenVLEndL 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
(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 # | |
type PS (ThenVL' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl sr) r) Source # | |
type PR (ThenVL' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl sr) r) Source # | |
type App (ThenVLEndSym plEnd prEnd s0r :: FunKind (Either a1 a2) (PResultEnd b2) -> Type) (s :: Either a1 a2) Source # | |
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 |