symbol-parser-0.2.0: Type level string parser combinators
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Type.Symbol.Parser.Then.VoidRight

Documentation

type family ThenVR pl pr where ... Source #

Equations

ThenVR '(plCh, plEnd, sl) '(prCh, prEnd, sr) = '(ThenVRChSym plCh prCh sr, ThenVREndSym prEnd, Left sl) 

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

Equations

ThenVRCh plCh prCh sr ch (Left sl) = ThenVRL sr ((plCh @@ ch) @@ sl) 
ThenVRCh plCh prCh _ ch (Right '(rl, sr)) = ThenVRR rl ((prCh @@ ch) @@ sr) 

type family ThenVRL sr resl where ... Source #

Equations

ThenVRL sr (Err el) = Err (Text "then: left error" :$$: el) 
ThenVRL sr (Cont sl) = Cont (Left sl) 
ThenVRL sr (Done rl) = Cont (Right '(rl, sr)) 

type family ThenVRR rl resr where ... Source #

Equations

ThenVRR rl (Err er) = Err (Text "then: right error" :$$: er) 
ThenVRR rl (Cont sr) = Cont (Right '(rl, sr)) 
ThenVRR rl (Done rr) = Done rl 

type family ThenVREnd prEnd s where ... Source #

Equations

ThenVREnd prEnd (Left sl) = Left (Text "thenvr: ended during left") 
ThenVREnd prEnd (Right '(rl, sr)) = ThenVREnd' rl (prEnd @@ sr) 

type family ThenVREnd' rl s where ... Source #

Equations

ThenVREnd' rl (Left er) = Left (Text "thenvr: right end error" :$$: er) 
ThenVREnd' rl (Right rr) = Right rl 

data ThenVRChSym plCh prCh sr f Source #

Instances

Instances details
type App (ThenVRChSym plCh prCh sr2 :: FunKind Char (Either sl (rl, sr1) ~> Result (Either sl (rl, sr1)) rl) -> Type) (f :: Char) Source # 
Instance details

Defined in Data.Type.Symbol.Parser.Then.VoidRight

type App (ThenVRChSym plCh prCh sr2 :: FunKind Char (Either sl (rl, sr1) ~> Result (Either sl (rl, sr1)) rl) -> Type) (f :: Char) = ThenVRChSym1 plCh prCh sr2 f

data ThenVRChSym1 plCh prCh sr ch s Source #

Instances

Instances details
type App (ThenVRChSym1 plCh prCh sr2 ch :: FunKind (Either sl (rl, sr1)) (Result (Either sl (rl, sr1)) rl) -> Type) (s :: Either sl (rl, sr1)) Source # 
Instance details

Defined in Data.Type.Symbol.Parser.Then.VoidRight

type App (ThenVRChSym1 plCh prCh sr2 ch :: FunKind (Either sl (rl, sr1)) (Result (Either sl (rl, sr1)) rl) -> Type) (s :: Either sl (rl, sr1)) = ThenVRCh plCh prCh sr2 ch s

data ThenVREndSym prEnd s Source #

Instances

Instances details
type App (ThenVREndSym prEnd :: FunKind (Either a2 (b2, a1)) (Either ErrorMessage b2) -> Type) (s :: Either a2 (b2, a1)) Source # 
Instance details

Defined in Data.Type.Symbol.Parser.Then.VoidRight

type App (ThenVREndSym prEnd :: FunKind (Either a2 (b2, a1)) (Either ErrorMessage b2) -> Type) (s :: Either a2 (b2, a1)) = ThenVREnd prEnd s