Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Expression provides a way of forming strongly types expression
languages from operators, via HFree
. This module is an explanation of how
that works, via a simple example.
This module is intended to be read via Haddock.
Synopsis
- data SimpleOp t a where
- data SimpleVar a where
- type SimpleExpr = HFree SimpleOp SimpleVar
- var :: String -> SimpleExpr Integer
- (^+) :: SimpleExpr Integer -> SimpleExpr Integer -> SimpleExpr Integer
- (^==) :: SimpleExpr Integer -> SimpleExpr Integer -> SimpleExpr Bool
- ifThenElse :: SimpleExpr Bool -> SimpleExpr Integer -> SimpleExpr Integer -> SimpleExpr Integer
- lit :: Integer -> SimpleExpr Integer
- exampleExpr :: SimpleExpr Integer
- exampleExpr2 :: SimpleExpr Integer
- evalXOrY :: SimpleVar a -> Maybe (Identity a)
- evalVarSymbolic :: SimpleVar a -> StateT (Map String (SBV Integer)) Symbolic (SBV a)
- evalSimpleExprSymbolic :: SimpleExpr a -> StateT (Map String (SBV Integer)) Symbolic (SBV a)
- examplePredicate :: Predicate
Operators
An operator is a type constructor op
of kind (* -> *) -> * -> *
. op t
a
should be seen as a way of combining t
-objects which has a result type
a
.
SimpleOp
is an example of an operator type.
data SimpleOp t a where Source #
An operator type has two arguments. t
is a type constructor used to refer to
expressions. a
is the semantic type of the expression formed by the operator.
Add :: t Integer -> t Integer -> SimpleOp t Integer | Given two int expressions, we may add them. Notice how we refer to expressions
recursively with the type constructor parameter |
Equal :: t Integer -> t Integer -> SimpleOp t Bool | Given two int expressions, we may compare them for equality. Notice the types of the arguments to the operator do not appear in the result type at all. |
IfThenElse :: t Bool -> t Integer -> t Integer -> SimpleOp t Integer | Operator constructors can have any number of arguments, and you can mix argument types. |
Literal :: Integer -> SimpleOp t Integer | An operator does not have to actually combine expressions. It may produce an
expression from a basic value, i.e. a literal int. |
Instances
HTraversable SimpleOp Source # | |
Defined in Language.Expression.Example | |
HFunctor SimpleOp Source # | |
HFoldableAt Identity SimpleOp Source # | |
HFoldableAt SBV SimpleOp Source # | |
Type Classes
Most useful operators are instances of HFunctor
(which provides hmap
) and
HTraversable
(which provides htraverse
). These are higher-ranked analogues
of Functor
and Traversable
from base
. Compare the type signatures of
fmap
and hmap
:
fmap
:: (Functor
f) => (a -> b) -> f a -> f bhmap
:: (HFunctor
h) => (forall b. s b -> t b) -> h s a -> h t a
fmap
transforms the *
-kinded type argument to f
, while hmap
transforms
the (* -> *)
-kinded type constructor argument to h
.
So in order for an operator to have an instance of HFunctor
, it must be
possible to swap out sub-expressions inside it. This is the case for our
SimpleOp
.
HTraversable
has a similar relationship with Traversable
. htraverse
adds an applicative context to 'hmap'\'s transformations:
traverse
:: (Traversable
t,Applicative
f) => (a -> f b) -> t a -> f (t b)htraverse
:: (HTraversable
h,Applicative
f) => (forall b. s b -> f (t b)) -> h s a -> f (h t a)
There is a default implementation of hmap
in terms of htraverse
.
Variables
As well as operators, expressions contain variables. Variables are also strongly
typed. A variable type v
has kind * -> *
. The type parameter tells us the
type of the value that the variable is meant to represent.
data SimpleVar a where Source #
Notice that a
is a phantom type here (and it will be for most variable type
constructors). It is only used to restrict the type of values that are
representable by these variables. In this case, we only want to be able to store
integers so the only constructor has return type Integer
. It also contains a
String
to be used as the variable name.
Expressions
A DSL
We can write simple wrapper functions to form a DSL for our expression language.
(^+) :: SimpleExpr Integer -> SimpleExpr Integer -> SimpleExpr Integer Source #
(^==) :: SimpleExpr Integer -> SimpleExpr Integer -> SimpleExpr Bool Source #
ifThenElse :: SimpleExpr Bool -> SimpleExpr Integer -> SimpleExpr Integer -> SimpleExpr Integer Source #
ifThenElse x y z =HWrap
(IfThenElse
x y z)
Example Expression
Expression Manipulation
If op
is an HFunctor
, then
is an HFree
opHMonad
. HMonad
defines
hpure
(c.f. pure
or return
):
hpure
:: (HMonad
h) => t a -> h t areturn
:: (Monad
m) => a -> m a
(>>=
) :: (Monad
m) => m a -> (a -> m b) -> m b (^>>=
) :: (HMonad
h) => h s a -> (forall b. s b -> h t b) -> h t a
In the case of
, HFree
ophpure
produces an expression containing a single
variable:
hpure
:: v a ->HFree
op v a
Substitution
^>>=
substitutes variables inside expressions.
Traversal
When op
is an HTraversable
, HFree
is also an HTraversable
. This can be
used, for example, to evaluate variables in an expression.
evalXOrY :: SimpleVar a -> Maybe (Identity a) Source #
This is a function that knows the value of variables with certain names. It will
return Nothing
if it doesn't know how to evaluate a particular variable.
evalXOrY (SimpleVar
"x") =Just
1 evalXOrY (SimpleVar
"y") =Just
2 evalXOrY _ =Nothing
It might seem strange that we can return
when the
function says it returns a Just
(Identity
1)
for polymorphic Maybe
(Identity
a)a
. This
works because the constructor SimpleVar
must be Integer
-valued, so when we match
on it, GHC generates the constraint a ~
and it will happily accept an
Integer
Integer
.
Notice that, for s ~
, SimpleVar
t ~
and Identity
f ~
,Maybe
evalXOrY :: forall a. s a -> f (t a)
This means that we can traverse using this function:
>>>
htraverse evalXOrY exampleExpr
htraverse evalXOrY exampleExpr :: Maybe (HFree SimpleOp Identity Integer) htraverse evalXOrY exampleExpr ~ Just (if (1 = 10) then 2 else 2 + 5)
>>>
htraverse evalXOrY exampleExpr2
htraverse evalXOrY exampleExpr2 :: Maybe (HFree SimpleOp Identity Integer) htraverse evalXOrY exampleExpr2 ~ Nothing
There was a variable (z
) that evalXOrY
didn't know how to evaluate, so the
traversal resulted in Nothing
!
Evaluating Expressions
The HFoldableAt
type class provides the mechanism for evaluating operators,
and hence expressions.
hfoldMap
:: (HFoldableAt
k h) => (forall b. t b -> k b) -> h t b -> k b
Implemented in terms of this is
hfoldTraverse
:: (HFoldableAt
k h,HTraversable
h,Applicative
f) => (forall b. t b -> f (k b)) -> h t a -> f (k a)hfoldTraverse
f =fmap
(hfoldMap
id
) .htraverse
f
This function will allow us to evaluate our expressions to ground values:
>>>
hfoldTraverse evalXOrY exampleExpr
Just (Identity 7)
>>>
hfoldTraverse evalXOrY exampleExpr2
Nothing
Evaluating Variables Symbolically
With the help of sbv
, we can evaluate expressions symbolically in order to
prove things about them.
Evaluating Expressions Symbolically
We need an instance of
to do symbolic
evaluation, implemented like so:HFoldableAt
SBV
SimpleOp
instanceHFoldableAt
SBV
SimpleOp
wherehfoldMap
=implHfoldMap
$ s -> case s ofAdd
x y -> x+
yEqual
x y -> x.==
yIfThenElse
x y z ->ite
x y zLiteral
x ->literal
x
evalSimpleExprSymbolic :: SimpleExpr a -> StateT (Map String (SBV Integer)) Symbolic (SBV a) Source #
Now we can evaluate expressions symbolically and use sbv
to prove things about
them.
evalSimpleExprSymbolic =hfoldTraverse
evalVarSymbolic
examplePredicate :: Predicate Source #
Let's ask sbv
to prove that our expression always returns a value no less than
the variable y
.
examplePredicate =flip
evalStateT
mempty
$ do expr <-evalSimpleExprSymbolic
exampleExpr
y <-evalSimpleExprSymbolic
(var
"y")return
(expr
.>=
y)
>>>
isTheorem examplePredicate
True