{-# LANGUAGE UndecidableInstances #-}
module Symparsec.Parser.Applicative
( type (<*>), type Pure
, type LiftA2
, type (*>), type (<*)
) where
import Symparsec.Parser.Common
import Symparsec.Parser.Functor
import DeFun.Function ( type IdSym, type ConstSym )
type (<*>) :: PParser (a ~> b) -> PParser a -> PParser b
infixl 4 <*>
data (<*>) l r s
type instance App (l <*> r) s = ApL r (l @@ s)
type ApL :: PParser a -> PReply (a ~> b) -> PReply b
type family ApL r rep where
ApL r ('Reply (OK fa) s) = (fa <$> r) @@ s
ApL r ('Reply (Err e) s) = 'Reply (Err e) s
type Pure :: a -> PParser a
data Pure a s
type instance App (Pure a) s = 'Reply (OK a) s
type LiftA2 :: (a ~> b ~> c) -> PParser a -> PParser b -> PParser c
type LiftA2 f l r = (f <$> l) <*> r
type (*>) :: PParser a -> PParser b -> PParser b
infixl 4 *>
type l *> r = (IdSym <$ l) <*> r
type (<*) :: PParser a -> PParser b -> PParser a
infixl 4 <*
type l <* r = LiftA2 ConstSym l r