ap-reflect-0.3: Partial evaluation reflection a la simple-reflect.

Safe HaskellSafe
LanguageHaskell2010

Debug.Reflect

Synopsis

Documentation

data a ~> b infixr 5 Source #

analog of (->)

Constructors

Fn String (a -> b)

name and function itself

Instances

Functor ((~>) a) Source # 

Methods

fmap :: (a -> b) -> (a ~> a) -> a ~> b #

(<$) :: a -> (a ~> b) -> a ~> a #

Show ((~>) a b) Source # 

Methods

showsPrec :: Int -> (a ~> b) -> ShowS #

show :: (a ~> b) -> String #

showList :: [a ~> b] -> ShowS #

fromFn :: (a ~> b) -> a -> b Source #

gets function

parens :: String -> String Source #

adds brackets

isInfixFn :: String -> Bool Source #

checks whether function is infix

showFn :: String -> String -> String Source #

shows function with its argument

makeFn2 :: Show a => String -> (a -> b -> c) -> a ~> (b ~> c) Source #

translates function (a -> b -> c) into (a ~> b ~> c)

makeBinOp :: Show a => String -> (a -> b -> c) -> a ~> (b ~> c) Source #

makes binary operation

data Ap b Source #

reflected expression

Constructors

Val b 
Show a => (Ap (a ~> b)) :$ (Ap a) 

Instances

Show a => Show (Ap a) Source # 

Methods

showsPrec :: Int -> Ap a -> ShowS #

show :: Ap a -> String #

showList :: [Ap a] -> ShowS #

isVal :: Ap a -> Bool Source #

checks whether expression is Val

balanceParens :: String -> String Source #

balances brackets

parensFr :: String -> String Source #

balances brackets

showOp :: String -> String -> String -> String Source #

shows operation application

showF :: String -> String -> String Source #

shows operation application

fmap' :: Functor f => (a ~> b) ~> (f a ~> f b) Source #

analog of fmap using (~>)

pure' :: Applicative f => a ~> f a Source #

analog of pure using (~>)

ap' :: (Show (f (a ~> b)), Applicative f) => f (a ~> b) ~> (f a ~> f b) Source #

analog of <*> using (~>)

(-$-) :: (Show (f a), Functor f) => (a ~> b) -> f a -> Ap (f b) infix 6 Source #

analog of <$>

(-*-) :: (Show (f (a ~> b)), Show (f a), Applicative f) => Ap (f (a ~> b)) -> f a -> Ap (f b) infixl 5 Source #

analog of <*>

pure'' :: (Show a, Applicative f) => a -> Ap (f a) Source #

analog of pure

fmap'' :: (Show (f a), Functor f) => (a ~> b) -> f a -> Ap (f b) Source #

analog of fmap

reduce'' :: Ap a -> Ap a Source #

reduces an expression

reduce' :: Show a => Ap a -> Ap a Source #

reduces (evaluates) an expression once

reductions :: Show a => Ap a -> [Ap a] Source #

gets all reduction steps when evaluating an expression