Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Symparsec.Parser.Then.VoidRight
Synopsis
- 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)
- 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
- type family pl :<*: pr where ...
- type ThenVR' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenVRChSym plCh prCh s0r) (ThenVREndSym plEnd prEnd s0r) (Left s0l)
- type family ThenVRCh plCh prCh s0r ch s where ...
- type family ThenVRChL prCh s0r ch resl where ...
- type EThenVRChL el = EIn "ThenVR(L)" el
- eThenVRChL :: SE el -> SE (EThenVRChL el)
- type family ThenVRChR rl resr where ...
- type EThenVRChR er = EIn "ThenVR(R)" er
- eThenVRChR :: SE er -> SE (EThenVRChR er)
- sThenVRChR :: srl rl -> SResult ssr srr resr -> SResult (SEither ssl (STuple2 srl ssr)) srl (ThenVRChR rl resr)
- sThenVRChSym :: SParserChSym ssl srl plCh -> SParserChSym ssr srr prCh -> ssr sr -> SParserChSym (SEither ssl (STuple2 srl ssr)) srl (ThenVRChSym plCh prCh sr)
- data ThenVRChSym plCh prCh s0r f
- data ThenVRChSym1 plCh prCh s0r ch s
- type family ThenVREnd plEnd prEnd s0r s where ...
- type family ThenVREndR rl res where ...
- type EThenVREndR er = EIn "ThenVR(R) end" er
- eThenVREndR :: SE er -> SE (EThenVREndR er)
- sThenVREndR :: srl rl -> SResultEnd srr res -> SResultEnd srl (ThenVREndR rl res)
- type family ThenVREndL prEnd s0r res where ...
- type EThenVREndL er = EIn "ThenVR(L) end" er
- eThenVREndL :: SE er -> SE (EThenVREndL er)
- sThenVREndSym :: SParserEndSym ssl srl plEnd -> SParserEndSym ssr srr prEnd -> ssr s0r -> SParserEndSym (SEither ssl (STuple2 srl ssr)) srl (ThenVREndSym plEnd prEnd s0r)
- data ThenVREndSym plEnd prEnd s0r s
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.
type ThenVR' plCh plEnd s0l prCh prEnd s0r = 'PParser (ThenVRChSym plCh prCh s0r) (ThenVREndSym plEnd prEnd s0r) (Left s0l) Source #
type EThenVRChL el = EIn "ThenVR(L)" el Source #
eThenVRChL :: SE el -> SE (EThenVRChL el) Source #
type EThenVRChR er = EIn "ThenVR(R)" er Source #
eThenVRChR :: SE er -> SE (EThenVRChR 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
(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 # | |
type App (ThenVRChSym plCh prCh s0r :: FunKind Char (Either sl (rl, sr) ~> PResult (Either sl (rl, sr)) rl) -> Type) (f :: Char) Source # | |
Defined in Symparsec.Parser.Then.VoidRight | |
type PS (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # | |
type PR (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # | |
data ThenVRChSym1 plCh prCh s0r ch s Source #
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 #
eThenVREndR :: SE er -> SE (EThenVREndR 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 #
eThenVREndL :: SE er -> SE (EThenVREndL 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
(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 # | |
type PS (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # | |
type PR (ThenVR' plCh plEnd s0l prCh prEnd s0r :: PParser (Either sl (r, sr)) r) Source # | |
type App (ThenVREndSym plEnd prEnd s0r :: FunKind (Either a1 (b1, a2)) (PResultEnd b1) -> Type) (s :: Either a1 (b1, a2)) Source # | |
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 |