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

Data.Type.Symbol.Parser.Then

Documentation

type family Then pl pr where ... Source #

Equations

Then '(plCh, plEnd, sl) '(prCh, prEnd, sr) = '(ThenChSym plCh prCh sr, ThenEndSym prEnd, Left sl) 

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

Equations

ThenCh plCh prCh sr ch (Left sl) = ThenL sr ((plCh @@ ch) @@ sl) 
ThenCh plCh prCh _ ch (Right '(rl, sr)) = ThenR rl ((prCh @@ ch) @@ sr) 

type family ThenL sr resl where ... Source #

Equations

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

type family ThenR rl resr where ... Source #

Equations

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

type family ThenEnd prEnd s where ... Source #

Equations

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

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

Equations

ThenEnd' rl (Left er) = Left (Text "then: right end error" :$$: er) 
ThenEnd' rl (Right rr) = Right '(rl, rr) 

data ThenChSym plCh prCh sr f Source #

Instances

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

Defined in Data.Type.Symbol.Parser.Then

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

data ThenChSym1 plCh prCh sr ch s Source #

Instances

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

Defined in Data.Type.Symbol.Parser.Then

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

data ThenEndSym prEnd s Source #

Instances

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

Defined in Data.Type.Symbol.Parser.Then

type App (ThenEndSym prEnd :: FunKind (Either a2 (k2, a1)) (Either ErrorMessage (k2, k1)) -> Type) (s :: Either a2 (k2, a1)) = ThenEnd prEnd s