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

Data.Type.Symbol.Parser.Then.VoidLeft

Documentation

type family ThenVL pl pr where ... Source #

Equations

ThenVL '(plCh, plEnd, sl) '(prCh, prEnd, sr) = '(ThenVLChSym plCh prCh sr, ThenVLEndSym prEnd, Left sl) 

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

Equations

ThenVLCh plCh prCh sr ch (Left sl) = ThenVLL sr ((plCh @@ ch) @@ sl) 
ThenVLCh plCh prCh _ ch (Right sr) = ThenVLR ((prCh @@ ch) @@ sr) 

type family ThenVLL sr resl where ... Source #

Equations

ThenVLL sr (Err el) = Err (Text "thenvl: left error" :$$: el) 
ThenVLL sr (Cont sl) = Cont (Left sl) 
ThenVLL sr (Done rl) = Cont (Right sr) 

type family ThenVLR resr where ... Source #

Equations

ThenVLR (Err er) = Err (Text "thenvl: right error" :$$: er) 
ThenVLR (Cont sr) = Cont (Right sr) 
ThenVLR (Done rr) = Done rr 

type family ThenVLEnd prEnd s where ... Source #

Equations

ThenVLEnd prEnd (Left sl) = Left (Text "thenvl: ended during left") 
ThenVLEnd prEnd (Right sr) = ThenVLEnd' (prEnd @@ sr) 

type family ThenVLEnd' s where ... Source #

Equations

ThenVLEnd' (Left er) = Left (Text "thenvl: right end error" :$$: er) 
ThenVLEnd' (Right rr) = Right rr 

data ThenVLChSym plCh prCh sr f Source #

Instances

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

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

type App (ThenVLChSym plCh prCh sr2 :: FunKind Char (Either sl sr1 ~> Result (Either sl sr1) rr) -> Type) (f :: Char) = ThenVLChSym1 plCh prCh sr2 f

data ThenVLChSym1 plCh prCh sr ch s Source #

Instances

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

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

type App (ThenVLChSym1 plCh prCh sr2 ch :: FunKind (Either sl sr1) (Result (Either sl sr1) rr) -> Type) (s :: Either sl sr1) = ThenVLCh plCh prCh sr2 ch s

data ThenVLEndSym prEnd s Source #

Instances

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

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

type App (ThenVLEndSym prEnd :: FunKind (Either a2 a1) (Either ErrorMessage b) -> Type) (s :: Either a2 a1) = ThenVLEnd prEnd s