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

Data.Type.Symbol.Parser.Isolate

Documentation

type family Isolate n p where ... Source #

Equations

Isolate n '(pCh, pEnd, s) = '(IsolateChSym pCh pEnd, IsolateEndSym, '(n, s)) 

type family IsolateCh pCh pEnd ch s where ... Source #

Equations

IsolateCh pCh pEnd ch '(0, s) = 'Err ('Text "cannot isolate 0 due to parser limitations") 
IsolateCh pCh pEnd ch '(1, s) = IsolateInnerEnd' pEnd ((pCh @@ ch) @@ s) 
IsolateCh pCh pEnd ch '(n, s) = IsolateInner n ((pCh @@ ch) @@ s) 

type family IsolateInnerEnd' pEnd res where ... Source #

Equations

IsolateInnerEnd' pEnd ('Err e) = 'Err e 
IsolateInnerEnd' pEnd ('Done r) = 'Done r 
IsolateInnerEnd' pEnd ('Cont s) = IsolateInnerEnd (pEnd @@ s) 

type family IsolateInnerEnd a where ... Source #

Equations

IsolateInnerEnd ('Left e) = 'Err e 
IsolateInnerEnd ('Right r) = 'Done r 

type family IsolateInner n a where ... Source #

Equations

IsolateInner _ ('Err e) = 'Err e 
IsolateInner _ ('Done _) = 'Err ('Text "isolated parser ended without consuming all input") 
IsolateInner n ('Cont s) = 'Cont '(n - 1, s) 

type family IsolateEnd s where ... Source #

Equations

IsolateEnd '(0, s) = 'Right '(0, s) 
IsolateEnd '(n, s) = 'Left ('Text "isolate wanted more than was there") 

data IsolateChSym pCh pEnd f Source #

Instances

Instances details
type App (IsolateChSym pCh pEnd :: FunKind Char ((Natural, s) ~> Result (Natural, s) r) -> Type) (f :: Char) Source # 
Instance details

Defined in Data.Type.Symbol.Parser.Isolate

type App (IsolateChSym pCh pEnd :: FunKind Char ((Natural, s) ~> Result (Natural, s) r) -> Type) (f :: Char) = IsolateChSym1 pCh pEnd f

data IsolateChSym1 pCh pEnd ch s Source #

Instances

Instances details
type App (IsolateChSym1 pCh pEnd ch :: FunKind (Natural, s1) (Result (Natural, s1) r) -> Type) (s2 :: (Natural, s1)) Source # 
Instance details

Defined in Data.Type.Symbol.Parser.Isolate

type App (IsolateChSym1 pCh pEnd ch :: FunKind (Natural, s1) (Result (Natural, s1) r) -> Type) (s2 :: (Natural, s1)) = IsolateCh pCh pEnd ch s2

data IsolateEndSym s Source #

Instances

Instances details
type App (IsolateEndSym :: FunKind (Natural, s1) (Either ErrorMessage r) -> Type) (s2 :: (Natural, s1)) Source # 
Instance details

Defined in Data.Type.Symbol.Parser.Isolate