symparsec-1.1.1: Type level string parser combinators
Safe HaskellSafe-Inferred
LanguageGHC2021

Symparsec.Parser.Apply

Synopsis

Documentation

type family f :<$>: p where ... Source #

Apply the given type function to the result.

Effectively fmap for parsers.

Equations

f :<$>: ('PParser pCh pEnd s0) = Apply' f pCh pEnd s0 

type Apply' f pCh pEnd s0 = 'PParser (ApplyChSym f pCh) (ApplyEndSym f pEnd) s0 Source #

type family ApplyCh f pCh ch s where ... Source #

Equations

ApplyCh f pCh ch s = ApplyCh' f ((pCh @@ ch) @@ s) 

type family ApplyCh' f res where ... Source #

Equations

ApplyCh' f (Cont s) = Cont s 
ApplyCh' f (Done r) = Done (f @@ r) 
ApplyCh' f (Err e) = Err e 

data ApplyChSym f pCh x Source #

Instances

Instances details
type App (ApplyChSym f pCh :: FunKind Char (s ~> PResult s r') -> Type) (x :: Char) Source # 
Instance details

Defined in Symparsec.Parser.Apply

type App (ApplyChSym f pCh :: FunKind Char (s ~> PResult s r') -> Type) (x :: Char) = ApplyChSym1 f pCh x

data ApplyChSym1 f pCh ch s Source #

Instances

Instances details
type App (ApplyChSym1 f pCh ch :: FunKind s1 (PResult s1 r') -> Type) (s2 :: s1) Source # 
Instance details

Defined in Symparsec.Parser.Apply

type App (ApplyChSym1 f pCh ch :: FunKind s1 (PResult s1 r') -> Type) (s2 :: s1) = ApplyCh f pCh ch s2

type family ApplyEnd f pEnd s where ... Source #

Equations

ApplyEnd f pEnd s = ApplyEnd' f (pEnd @@ s) 

type family ApplyEnd' f res where ... Source #

Equations

ApplyEnd' f (Right r) = Right (f @@ r) 
ApplyEnd' f (Left e) = Left e 

data ApplyEndSym f pEnd s Source #

Instances

Instances details
type App (ApplyEndSym f pEnd :: FunKind s1 (PResultEnd r') -> Type) (s2 :: s1) Source # 
Instance details

Defined in Symparsec.Parser.Apply

type App (ApplyEndSym f pEnd :: FunKind s1 (PResultEnd r') -> Type) (s2 :: s1) = ApplyEnd f pEnd s2