Haskell-Use instance function for pattern matching - haskell

I want to implement a simple expression tree with plus and minus operations.
I implemented a class "Group" with the following function signatures:
-- type class Group a ---------------------------------------------------------
class (Eq a, Show a, Read a, Num a) => Group a where
add :: a -> a -> a
identity :: a
invers :: a -> a
Add gets two elements and returns the sum (e.g. 4+7 = 11), identity is a special element that leaves other elements unchanged (i.e. 0 because 3 + 0 = 3) and invers calculates the inverse of a element (e.g. inverse of 3 is -3).
The instance of this class is for values of type integer, therefore it looks like this:
-- Group Integer ----------------------------------------------------------------
instance Group Integer where
add x y = x+y
invers x = -x
identity = 0
The expression tree should consist of the following data elements:
-- expression tree with values having Group property ---------------------------
data Expr a = Lit a | Invers (Expr a) | Add (Expr a) (Expr a) deriving (Eq, Read)
The Lit constructor gets an element of some type (e.g. an Integer value), Invers gets a sub expression and Add gets two sub expressions.
What I want to achieve now is to implement a function called "simplify". It should simplify any expression based on the following axioms:
x `add` idenity = x
idenity `add` x = x
x `add` (invers x) = identity
(invers x) `add` x = identity
What I've implemented so far is the following:
-- simplify --------------------------------------------------------------------
-- simplify simplifies expression trees applying Group laws as follows ---------
-- add x zero = x
-- add zero x = x
-- add x (minus x) = zero
-- add (minus x) x = zero
----- Match for any axiom ----
simplify :: (Group a) => Expr a -> Expr a
simplify (Add(Lit x) (Invers (Lit y))) | x == y = Lit identity
simplify (Invers (Invers (Lit x))) = Lit x
simplify (Invers (Lit identity)) = Lit identity
simplify (Add(Lit x) (Lit identity)) = Lit x
simplify (Add(Lit identity) (Lit x)) = Lit x
----- No axiom found, so call simplify recusively ----
simplify (Invers x) = simplify (x) -- x is a sub expression
simplify (Add x y) = Add (simplify x) (simplify y) -- x and/or y are sub expressions
My problem is that I cannot match for the "identity" element on the left side of the simplify function.
The line
simplify (Invers (Lit identity)) = Lit identity
would be the same as
simplify (Invers (Lit x)) = Lit x
since identity is any variable in this scope. Is there any possibility to match against the identity function of the "Group" class?
Thanks much.

Why not just simplify (Inverse (Lit x)) | x == identity = identity, or am I misunderstanding your problem? [bennofs]

Related

How to reduce code duplication when dealing with recursive sum types

I am currently working on a simple interpreter for a programming language and I have a data type like this:
data Expr
= Variable String
| Number Int
| Add [Expr]
| Sub Expr Expr
And I have many functions that do simple things like:
-- Substitute a value for a variable
substituteName :: String -> Int -> Expr -> Expr
substituteName name newValue = go
where
go (Variable x)
| x == name = Number newValue
go (Add xs) =
Add $ map go xs
go (Sub x y) =
Sub (go x) (go y)
go other = other
-- Replace subtraction with a constant with addition by a negative number
replaceSubWithAdd :: Expr -> Expr
replaceSubWithAdd = go
where
go (Sub x (Number y)) =
Add [go x, Number (-y)]
go (Add xs) =
Add $ map go xs
go (Sub x y) =
Sub (go x) (go y)
go other = other
But in each of these functions, I have to repeat the part that calls the code recursively with just a small change to one part of the function. Is there any existing way to do this more generically? I would rather not have to copy and paste this part:
go (Add xs) =
Add $ map go xs
go (Sub x y) =
Sub (go x) (go y)
go other = other
And just change a single case each time because it seems inefficient to duplicate code like this.
The only solution I could come up with is to have a function that calls a function first on the whole data structure and then recursively on the result like this:
recurseAfter :: (Expr -> Expr) -> Expr -> Expr
recurseAfter f x =
case f x of
Add xs ->
Add $ map (recurseAfter f) xs
Sub x y ->
Sub (recurseAfter f x) (recurseAfter f y)
other -> other
substituteName :: String -> Int -> Expr -> Expr
substituteName name newValue =
recurseAfter $ \case
Variable x
| x == name -> Number newValue
other -> other
replaceSubWithAdd :: Expr -> Expr
replaceSubWithAdd =
recurseAfter $ \case
Sub x (Number y) ->
Add [x, Number (-y)]
other -> other
But I feel like there should probably be a simpler way to do this already. Am I missing something?
Congratulations, you just rediscovered anamorphisms!
Here's your code, rephrased so that it works with the recursion-schemes package. Alas, it's not shorter, since we need some boilerplate to make the machinery work. (There might be some automagic way to avoid the boilerplate, e.g. using generics. I simply do not know.)
Below, your recurseAfter is replaced with the standard ana.
We first define your recursive type, as well as the functor it is the fixed point of.
{-# LANGUAGE DeriveFunctor, TypeFamilies, LambdaCase #-}
{-# OPTIONS -Wall #-}
module AnaExpr where
import Data.Functor.Foldable
data Expr
= Variable String
| Number Int
| Add [Expr]
| Sub Expr Expr
deriving (Show)
data ExprF a
= VariableF String
| NumberF Int
| AddF [a]
| SubF a a
deriving (Functor)
Then we connect the two with a few instances so that we can unfold Expr into the isomorphic ExprF Expr, and fold it back.
type instance Base Expr = ExprF
instance Recursive Expr where
project (Variable s) = VariableF s
project (Number i) = NumberF i
project (Add es) = AddF es
project (Sub e1 e2) = SubF e1 e2
instance Corecursive Expr where
embed (VariableF s) = Variable s
embed (NumberF i) = Number i
embed (AddF es) = Add es
embed (SubF e1 e2) = Sub e1 e2
Finally, we adapt your original code, and add a couple of tests.
substituteName :: String -> Int -> Expr -> Expr
substituteName name newValue = ana $ \case
Variable x | x == name -> NumberF newValue
other -> project other
testSub :: Expr
testSub = substituteName "x" 42 (Add [Add [Variable "x"], Number 0])
replaceSubWithAdd :: Expr -> Expr
replaceSubWithAdd = ana $ \case
Sub x (Number y) -> AddF [x, Number (-y)]
other -> project other
testReplace :: Expr
testReplace = replaceSubWithAdd
(Add [Sub (Add [Variable "x", Sub (Variable "y") (Number 34)]) (Number 10), Number 4])
An alternative could be to define ExprF a only, and then derive type Expr = Fix ExprF. This saves some of the boilerplate above (e.g. the two instances), at the cost of having to use Fix (VariableF ...) instead of Variable ..., as well as the analogous for the other constructors.
One could further alleviate that using pattern synonyms (at the cost of a little more boilerplate, though).
Update: I finally found the automagic tool, using template Haskell. This makes the whole code reasonably short. Note that the ExprF functor and the two instances above still exist under the hood, and we still have to use them. We only save the hassle of having to define them manually, but that alone saves a lot of effort.
{-# LANGUAGE DeriveFunctor, DeriveTraversable, TypeFamilies, LambdaCase, TemplateHaskell #-}
{-# OPTIONS -Wall #-}
module AnaExpr where
import Data.Functor.Foldable
import Data.Functor.Foldable.TH
data Expr
= Variable String
| Number Int
| Add [Expr]
| Sub Expr Expr
deriving (Show)
makeBaseFunctor ''Expr
substituteName :: String -> Int -> Expr -> Expr
substituteName name newValue = ana $ \case
Variable x | x == name -> NumberF newValue
other -> project other
testSub :: Expr
testSub = substituteName "x" 42 (Add [Add [Variable "x"], Number 0])
replaceSubWithAdd :: Expr -> Expr
replaceSubWithAdd = ana $ \case
Sub x (Number y) -> AddF [x, Number (-y)]
other -> project other
testReplace :: Expr
testReplace = replaceSubWithAdd
(Add [Sub (Add [Variable "x", Sub (Variable "y") (Number 34)]) (Number 10), Number 4])
As an alternative approach, this is also a typical use case for the uniplate package. It can use Data.Data generics rather than Template Haskell to generate the boilerplate, so if you derive Data instances for your Expr:
import Data.Data
data Expr
= Variable String
| Number Int
| Add [Expr]
| Sub Expr Expr
deriving (Show, Data)
then the transform function from Data.Generics.Uniplate.Data applies a function recursively to each nested Expr:
import Data.Generics.Uniplate.Data
substituteName :: String -> Int -> Expr -> Expr
substituteName name newValue = transform f
where f (Variable x) | x == name = Number newValue
f other = other
replaceSubWithAdd :: Expr -> Expr
replaceSubWithAdd = transform f
where f (Sub x (Number y)) = Add [x, Number (-y)]
f other = other
Note that in replaceSubWithAdd in particular, the function f is written to perform a non-recursive substitution; transform makes it recursive in x :: Expr, so it's doing the same magic to the helper function as ana does in #chi's answer:
> substituteName "x" 42 (Add [Add [Variable "x"], Number 0])
Add [Add [Number 42],Number 0]
> replaceSubWithAdd (Add [Sub (Add [Variable "x",
Sub (Variable "y") (Number 34)]) (Number 10), Number 4])
Add [Add [Add [Variable "x",Add [Variable "y",Number (-34)]],Number (-10)],Number 4]
>
This is no shorter than #chi's Template Haskell solution. One potential advantage is that uniplate provides some additional functions that may be helpful. For example, if you use descend in place of transform, it transforms only the immediate children which can give you control over where the recursion happens, or you can use rewrite to re-transform the result of transformations until you reach a fixed point. One potential disadvantage is that "anamorphism" sounds way cooler than "uniplate".
Full program:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Data -- in base
import Data.Generics.Uniplate.Data -- package uniplate
data Expr
= Variable String
| Number Int
| Add [Expr]
| Sub Expr Expr
deriving (Show, Data)
substituteName :: String -> Int -> Expr -> Expr
substituteName name newValue = transform f
where f (Variable x) | x == name = Number newValue
f other = other
replaceSubWithAdd :: Expr -> Expr
replaceSubWithAdd = transform f
where f (Sub x (Number y)) = Add [x, Number (-y)]
f other = other
replaceSubWithAdd1 :: Expr -> Expr
replaceSubWithAdd1 = descend f
where f (Sub x (Number y)) = Add [x, Number (-y)]
f other = other
main = do
print $ substituteName "x" 42 (Add [Add [Variable "x"], Number 0])
print $ replaceSubWithAdd e
print $ replaceSubWithAdd1 e
where e = Add [Sub (Add [Variable "x", Sub (Variable "y") (Number 34)])
(Number 10), Number 4]

Haskell: Is it possible to identify which function was passed as parameter to a high order function?

I want to idenfity what function was passed as parameter to a high-order function.
How can i do that? Using pattern matching?
I want to do something like the following code:
add x y = x+y
sub x y = x-y
myFunc :: (a->a->a) -> a -> a -> IO a
myFunc add x y = do print "add was performed"
add x y
myFunc sub x y = do print "sub was performed"
sum x y
myFunc f x y = do print "another function was performed"
f x y
If this is not possible, does anyone has other idea to do that?
No, this is not possible.
You could achieve something to that effect by having a data type which represents the operation, maybe
data Operation
= Add (a -> a -> a)
| Sub (a -> a -> a)
| Other (a -> a -> a)
myFunc :: Operation -> a -> a -> IO a
myFunc (Add f) x y = do print "add was performed"
return (f x y)
myFunc (Sub f) x y = do print "sub was performed"
return (f x y)
myFunc (Other f) x y = do print "another function was performed"
return (f x y)
It's not possible to do exactly what you requested. I would recommend that you instead make an embedded domain-specific language (EDSL) and write one or more interpreters for it. The most common approach is to represent the EDSL using an algebraic datatype or (in more complicated situations) a generalized algebraic datatype. Here you might have something like
data Expr a = Lit a
| BinOp (Op a) (Expr a) (Expr a)
deriving (Show)
data Op a = Add
| Sub
| Other (a -> a -> a)
instance Show (Op a) where
show Add = "Add"
show Sub = "Sub"
show Other{} = "Other"
Now you can write an evaluator that takes an Expr a and performs the requested operations:
evalExpr :: Num a => Expr a -> a
evalExpr (Lit x) = x
evalExpr (BinOp op e1 e2) = runOp op (evalExpr e1) (evalExpr e2)
runOp :: Num a => Op a -> a -> a -> a
runOp Add a b = a + b
runOp Sub a b = a - b
runOp (Other f) a b = f a b
You can add tracing too:
evalExpr' :: (Num a, MonadWriter [(Expr a, a)] m) => Expr a -> m a
evalExpr' e = do
result <- case e of
Lit a -> return a
BinOp op e1 e2 -> runOp op <$> evalExpr' e1 <*> evalExpr' e2
tell [(e, result)]
return result
Sample use:
*Write> runWriter $ evalExpr' (BinOp Add (Lit 3) (BinOp Sub (Lit 4) (Lit 5)))
(2,[(Lit 3,3),(Lit 4,4),(Lit 5,5),(BinOp Sub (Lit 4) (Lit 5),-1),(BinOp Add (Lit 3) (BinOp Sub (Lit 4) (Lit 5)),2)])
For convenience, you can write
instance Num a => Num (Expr a) where
fromInteger = Lit . fromInteger
(+) = BinOp Add
(-) = BinOp Sub
Then the above can be abbreviated
*Write Control.Monad.Writer> runWriter $ evalExpr' (3 + (4-5))
(2,[(Lit 3,3),(Lit 4,4),(Lit 5,5),(BinOp Sub (Lit 4) (Lit 5),-1),(BinOp Add (Lit 3) (BinOp Sub (Lit 4) (Lit 5)),2)])
Maybe to simplify and not to change a lot the overall look of your code, if it's already a long project and that's a concern, you could do something like:
add x y = x+y
sub x y = x-y
myFunc :: (Eq a, Num a) => (a->a->a) -> a -> a -> IO a
myFunc f x y = if (add x y) == (f x y) then
do print "add was performed"
return (add x y)
else if (sub x y) == (f x y) then
do print "sub was performed"
return (sub x y)
else
do print "another function was performed"
return (f x y)
It works, the only problem is that you wont be able to diferentiate for example an add 2 1 from a multiplication 2 1, so if thats a possibility you can throw new cases in there to cover all important grounds, like instead of only comparing add x y = f x y, also compare add y x with f y x. With some thought it will work 100% of the time.

Reusing patterns in pattern guards or case expressions

My Haskell project includes an expression evaluator, which for the purposes of this question can be simplified to:
data Expression a where
I :: Int -> Expression Int
B :: Bool -> Expression Bool
Add :: Expression Int -> Expression Int -> Expression Int
Mul :: Expression Int -> Expression Int -> Expression Int
Eq :: Expression Int -> Expression Int -> Expression Bool
And :: Expression Bool -> Expression Bool -> Expression Bool
Or :: Expression Bool -> Expression Bool -> Expression Bool
If :: Expression Bool -> Expression a -> Expression a -> Expression a
-- Reduces an Expression down to the simplest representation.
reduce :: Expression a -> Expression a
-- ... implementation ...
The straightforward approach to implementing this is to write a case expression to recursively evaluate and pattern match, like so:
reduce (Add x y) = case (reduce x, reduce y) of
(I x', I y') -> I $ x' + y'
(x', y') -> Add x' y'
reduce (Mul x y) = case (reduce x, reduce y) of
(I x', I y') -> I $ x' * y'
(x', y') -> Mul x' y'
reduce (And x y) = case (reduce x, reduce y) of
(B x', B y') -> B $ x' && y'
(x', y') -> And x' y'
-- ... and similarly for other cases.
To me, that definition looks somewhat awkward, so I then rewrote the definition using pattern guards, like so:
reduce (Add x y) | I x' <- reduce x
, I y' <- reduce y
= I $ x' + y'
I think this definition looks cleaner compared to the case expression, but when defining multiple patterns for different constructors, the pattern is repeated multiple times.
reduce (Add x y) | I x' <- reduce x
, I y' <- reduce y
= I $ x' + y'
reduce (Mul x y) | I x' <- reduce x
, I y' <- reduce y
= I $ x' * y'
Noting these repeated patterns, I was hoping there would be some syntax or structure that could cut down on the repetition in the pattern matching. Is there a generally accepted method to simplify these definitions?
Edit: after reviewing the pattern guards, I've realised they don't work as a drop-in replacement here. Although they provide the same result when x and y can be reduced to I _, they do not reduce any values when the pattern guards do not match. I would still like reduce to simplify subexpressions of Add et al.
One partial solution, which I've used in a similar situation, is to extract the logic into a "lifting" function that takes a normal Haskell operation and applies it to your language's values. This abstracts over the wrappping/unwrapping and resulting error handling.
The idea is to create two typeclasses for going to and from your custom type, with appropriate error handling. Then you can use these to create a liftOp function that could look like this:
liftOp :: (Extract a, Extract b, Pack c) => (a -> b -> c) ->
(Expression a -> Expression b -> Expression c)
liftOp err op a b = case res of
Nothing -> err a' b'
Just res -> pack res
where res = do a' <- extract $ reduce' a
b' <- extract $ reduce' b
return $ a' `op` b'
Then each specific case looks like this:
Mul x y -> liftOp Mul (*) x y
Which isn't too bad: it isn't overly redundant. It encompasses the information that matters: Mul gets mapped to *, and in the error case we just apply Mul again.
You would also need instances for packing and unpacking, but these are useful anyhow. One neat trick is that these can also let you embed functions in your DSL automatically, with an instance of the form (Extract a, Pack b) => Pack (a -> b).
I'm not sure this will work exactly for your example, but I hope it gives you a good starting point. You might want to wire additional error handling through the whole thing, but the good news is that most of that gets folded into the definition of pack, unpack and liftOp, so it's still pretty centralized.
I wrote up a similar solution for a related (but somewhat different) problem. It's also a way to handle going back and forth between native Haskell values and an interpreter, but the interpreter is structured differently. Some of the same ideas should still apply though!
This answer is inspired by rampion's follow-up question, which suggests the following function:
step :: Expression a -> Expression a
step x = case x of
Add (I x) (I y) -> I $ x + y
Mul (I x) (I y) -> I $ x * y
Eq (I x) (I y) -> B $ x == y
And (B x) (B y) -> B $ x && y
Or (B x) (B y) -> B $ x || y
If (B b) x y -> if b then x else y
z -> z
step looks at a single term, and reduces it if everything needed to reduce it is present. Equiped with step, we only need a way to replace a term everywhere in the expression tree. We can start by defining a way to apply a function inside every term.
{-# LANGUAGE RankNTypes #-}
emap :: (forall a. Expression a -> Expression a) -> Expression x -> Expression x
emap f x = case x of
I a -> I a
B a -> B a
Add x y -> Add (f x) (f y)
Mul x y -> Mul (f x) (f y)
Eq x y -> Eq (f x) (f y)
And x y -> And (f x) (f y)
Or x y -> Or (f x) (f y)
If x y z -> If (f x) (f y) (f z)
Now, we need to apply a function everywhere, both to the term and everywhere inside the term. There are two basic possibilities, we could apply the function to the term before applying it inside or we could apply the function afterwards.
premap :: (forall a. Expression a -> Expression a) -> Expression x -> Expression x
premap f = emap (premap f) . f
postmap :: (forall a. Expression a -> Expression a) -> Expression x -> Expression x
postmap f = f . emap (postmap f)
This gives us two possibilities for how to use step, which I will call shorten and reduce.
shorten = premap step
reduce = postmap step
These behave a little differently. shorten removes the innermost level of terms, replacing them with literals, shortening the height of the expression tree by one. reduce completely evaluates the expression tree to a literal. Here's the result of iterating each of these on the same input
"shorten"
If (And (B True) (Or (B False) (B True))) (Add (I 1) (Mul (I 2) (I 3))) (I 0)
If (And (B True) (B True)) (Add (I 1) (I 6)) (I 0)
If (B True) (I 7) (I 0)
I 7
"reduce"
If (And (B True) (Or (B False) (B True))) (Add (I 1) (Mul (I 2) (I 3))) (I 0)
I 7
Partial reduction
Your question implies that you sometimes expect that expressions can't be reduced completely. I'll extend your example to include something to demonstrate this case, by adding a variable, Var.
data Expression a where
Var :: Expression Int
...
We will need to add support for Var to emap:
emap f x = case x of
Var -> Var
...
bind will replace the variable, and evaluateFor performs a complete evaluation, traversing the expression only once.
bind :: Int -> Expression a -> Expression a
bind a x = case x of
Var -> I a
z -> z
evaluateFor :: Int -> Expression a -> Expression a
evaluateFor a = postmap (step . bind a)
Now reduce iterated on an example containing a variable produces the following output
"reduce"
If (And (B True) (Or (B False) (B True))) (Add (I 1) (Mul Var (I 3))) (I 0)
Add (I 1) (Mul Var (I 3))
If the output expression from the reduction is evaluated for a specific value of Var, we can reduce the expression all the way to a literal.
"evaluateFor 5"
Add (I 1) (Mul Var (I 3))
I 16
Applicative
emap can instead be written in terms of an Applicative Functor, and postmap can be made into a generic piece of code suitable for other data types than expressions. How to do so is described in this answer to rampion's follow-up question.

How to evaluate expressions in Haskell

I understand how to create and evaluate a simple data-type Expr. For example like this:
data Expr = Lit Int | Add Expr Expr | Sub Expr Expr | [...]
eval :: Expr -> Int
eval (Lit x) = x
eval (Add x y) = eval x + eval y
eval (Sub x y) = eval x - eval y
So here is my question: How can I add Variables to this Expr type, which should be evaluated for its assigned value? It should look like this:
data Expr = Var Char | Lit Int | Add Expr Expr [...]
type Assignment = Char -> Int
eval :: Expr -> Assignment -> Int
How do I have to do my eval function now for (Var Char) and (Add Expr Expr)? I think I figured out the easiest, how to do it for Lit already.
eval (Lit x) _ = x
For (Var Char) I tried a lot, but I cant get an Int out of an Assignment.. Thought It would work like this:
eval (Var x) (varname number) = number
Well if you model your enviroment as
type Env = Char -> Int
Then all you have is
eval (Var c) env = env c
But this isn't really "correct". For one, what happens with unbound variables? So perhaps a more accurate type is
type Env = Char -> Maybe Int
emptyEnv = const Nothing
And now we can see whether a variable is unbound
eval (Var c) env = maybe handleUnboundCase id (env c)
And now we can use handleUnboundCase to do something like assign a default value, blow up the program, or make monkeys climb out of your ears.
The final question to ask is "how are variables bound?". If you where looking for a "let" statement like we have in Haskell, then we can use a trick known as HOAS (higher order abstract syntax).
data Exp = ... | Let Exp (Exp -> Exp)
The HOAS bit is that (Exp -> Exp). Essentially we use Haskell's name-binding to implement our languages. Now to evaluate a let expression we do
eval (Let val body) = body val
This let's us dodge Var and Assignment by relying on Haskell to resolve the variable name.
An example let statement in this style might be
Let 1 $ \x -> x + x
-- let x = 1 in x + x
The biggest downside here is that modelling mutability is a royal pain, but this was already the case when relying on the Assignment type vs a concrete map.
You need to apply your Assignment function to the variable name to get the Int:
eval (Var x) f = f x
This works because f :: Char -> Int and x:: Char, so you can just do f x to get an Int.
Pleasingly this will work across a collection of variable names.
Example
ass :: Assignment
ass 'a' = 1
ass 'b' = 2
meaning that
eval ((Add (Var 'a') (Var 'b')) ass
= eval (Var 'a') ass + eval (Var 'b') ass
= ass 'a' + ass 'b'
= 1 + 2
= 3
Pass the assignment functions through to other calls of eval
You need to keep passing the assignment function around until you get integers:
eval (Add x y) f = eval x f + eval y f
Different order?
If you're allowed to change the types, it seems more logical to me to put the assignment function first and the data second:
eval :: Assignment -> Expr -> Int
eval f (Var x) = f x
eval f (Add x y) = eval f x + eval f y
...but I guess you can think of it as a constant expression with varying variables (feels imperative)rather than a constant set of values across a range of expressions (feels like referential transparency).
I would recommend using Map from Data.Map instead. You could implement it something like
import Data.Map (Map)
import qualified Data.Map as M -- A lot of conflicts with Prelude
-- Used to map operations through Maybe
import Control.Monad (liftM2)
data Expr
= Var Char
| Lit Int
| Add Expr Expr
| Sub Expr Expr
| Mul Expr Expr
deriving (Eq, Show, Read)
type Assignment = Map Char Int
eval :: Expr -> Assignment -> Maybe Int
eval (Lit x) _ = Just x
eval (Add x y) vars = liftM2 (+) (eval x vars) (eval y vars)
eval (Sub x y) vars = liftM2 (-) (eval x vars) (eval y vars)
eval (Mul x y) vars = liftM2 (*) (eval x vars) (eval y vars)
eval (Var x) vars = M.lookup x vars
But this looks clunky, and we'd have to keep using liftM2 op every time we added an operation. Let's clean it up a bit with some helpers
(|+|), (|-|), (|*|) :: (Monad m, Num a) => m a -> m a -> m a
(|+|) = liftM2 (+)
(|-|) = liftM2 (-)
(|*|) = liftM2 (*)
infixl 6 |+|, |-|
infixl 7 |*|
eval :: Expr -> Assignment -> Maybe Int
eval (Lit x) _ = return x -- Use generic return instead of explicit Just
eval (Add x y) vars = eval x vars |+| eval y vars
eval (Sub x y) vars = eval x vars |-| eval y vars
eval (Mul x y) vars = eval x vars |*| eval y vars
eval (Var x) vars = M.lookup x vars
That's a better, but we still have to pass around the vars everywhere, this is ugly to me. Instead, we can use the ReaderT monad from the mtl package. The ReaderT monad (and the non-transformer Reader) is a very simple monad, it exposes a function ask that returns the value you pass in when it's run, where all you can do is "read" this value, and is usually used for running an application with static configuration. In this case, our "config" is an Assignment.
This is where the liftM2 operators really come in handy
-- This is a long type signature, let's make an alias
type ExprM a = ReaderT Assignment Maybe a
-- Eval still has the same signature
eval :: Expr -> Assignment -> Maybe Int
eval expr vars = runReaderT (evalM expr) vars
-- evalM is essentially our old eval function
evalM :: Expr -> ExprM Int
evalM (Lit x) = return x
evalM (Add x y) = evalM x |+| evalM y
evalM (Sub x y) = evalM x |-| evalM y
evalM (Mul x y) = evalM x |*| evalM y
evalM (Var x) = do
vars <- ask -- Get the static "configuration" that is our list of vars
lift $ M.lookup x vars
-- or just
-- evalM (Var x) = ask >>= lift . M.lookup x
The only thing that we really changed was that we have to do a bit extra whenever we encounter a Var x, and we removed the vars parameter. I think this makes evalM very elegant, since we only access the Assignment when we need it, and we don't even have to worry about failure, it's completely taken care of by the Monad instance for Maybe. There isn't a single line of error handling logic in this entire algorithm, yet it will gracefully return Nothing if a variable name is not present in the Assignment.
Also, consider if later you wanted to switch to Doubles and add division, but you also want to return an error code so you can determine if there was a divide by 0 error or a lookup error. Instead of Maybe Double, you could use Either ErrorCode Double where
data ErrorCode
= VarUndefinedError
| DivideByZeroError
deriving (Eq, Show, Read)
Then you could write this module as
data Expr
= Var Char
| Lit Double
| Add Expr Expr
| Sub Expr Expr
| Mul Expr Expr
| Div Expr Expr
deriving (Eq, Show, Read)
type Assignment = Map Char Double
data ErrorCode
= VarUndefinedError
| DivideByZeroError
deriving (Eq, Show, Read)
type ExprM a = ReaderT Assignment (Either ErrorCode) a
eval :: Expr -> Assignment -> Either ErrorCode Double
eval expr vars = runReaderT (evalM expr) vars
throw :: ErrorCode -> ExprM a
throw = lift . Left
evalM :: Expr -> ExprM Double
evalM (Lit x) = return x
evalM (Add x y) = evalM x |+| evalM y
evalM (Sub x y) = evalM x |-| evalM y
evalM (Mul x y) = evalM x |*| evalM y
evalM (Div x y) = do
x' <- evalM x
y' <- evalM y
if y' == 0
then throw DivideByZeroError
else return $ x' / y'
evalM (Var x) = do
vars <- ask
maybe (throw VarUndefinedError) return $ M.lookup x vars
Now we do have explicit error handling, but it isn't bad, and we've been able to use maybe to avoid explicitly matching on Just and Nothing.
This is a lot more information than you really need to solve this problem, I just wanted to present an alternative solution that uses the monadic properties of Maybe and Either to provide easy error handling and use ReaderT to clean up that noise of passing an Assignment argument around everywhere.

Conversion from lambda term to combinatorial term

Suppose there are some data types to express lambda and combinatorial terms:
data Lam α = Var α -- v
| Abs α (Lam α) -- λv . e1
| App (Lam α) (Lam α) -- e1 e2
deriving (Eq, Show)
infixl 0 :#
data SKI α = V α -- x
| SKI α :# SKI α -- e1 e2
| I -- I
| K -- K
| S -- S
deriving (Eq, Show)
There is also a function to get a list of lambda term's free variables:
fv ∷ Eq α ⇒ Lam α → [α]
fv (Var v) = [v]
fv (Abs x e) = filter (/= x) $ fv e
fv (App e1 e2) = fv e1 ++ fv e2
To convert lambda term to combinatorial term abstract elimination rules could be usefull:
convert ∷ Eq α ⇒ Lam α → SKI α
1) T[x] => x
convert (Var x) = V x
2) T[(E₁ E₂)] => (T[E₁] T[E₂])
convert (App e1 e2) = (convert e1) :# (convert e2)
3) T[λx.E] => (K T[E]) (if x does not occur free in E)
convert (Abs x e) | x `notElem` fv e = K :# (convert e)
4) T[λx.x] => I
convert (Abs x (Var y)) = if x == y then I else K :# V y
5) T[λx.λy.E] => T[λx.T[λy.E]] (if x occurs free in E)
convert (Abs x (Abs y e)) | x `elem` fv e = convert (Abs x (convert (Abs y e)))
6) T[λx.(E₁ E₂)] => (S T[λx.E₁] T[λx.E₂])
convert (Abs x (App y z)) = S :# (convert (Abs x y)) :# (convert (Abs x z))
convert _ = error ":["
This definition is not valid because of 5):
Couldn't match expected type `Lam α' with actual type `SKI α'
In the return type of a call of `convert'
In the second argument of `Abs', namely `(convert (Abs y e))'
In the first argument of `convert', namely
`(Abs x (convert (Abs y e)))'
So, what I have now is:
> convert $ Abs "x" $ Abs "y" $ App (Var "y") (Var "x")
*** Exception: :[
What I want is (hope I calculate it right):
> convert $ Abs "x" $ Abs "y" $ App (Var "y") (Var "x")
S :# (S (KS) (S (KK) I)) (S (KK) I)
Question:
If lambda term and combinatorial term have a different types of expression, how 5) could be formulated right?
Let's consider the equation T[λx.λy.E] => T[λx.T[λy.E]].
We know the result of T[λy.E] is an SKI expression. Since it has been produced by one of the cases 3, 4 or 6, it is either I or an application (:#).
Thus the outer T in T[λx.T[λy.E]] must be one of the cases 3 or 6. You can perform this case analysis in the code. I'm sorry but I don't have the time to write it out.
Here it's better to have a common data type for combinators and lambda expressions. Notice that your types already have significant overlap (Var, App), and it doesn't hurt to have combinators in lambda expressions.
The only possibility we want to eliminate is having lambda abstractions in combinator terms. We can forbid them using indexed types.
In the following code the type of a term is parameterised by the number of nested lambda abstractions in that term. The convert function returns Term Z a, where Z means zero, so there are no lambda abstractions in the returned term.
For more information about singleton types (which are used a bit here), see the paper Dependently Typed Programming with Singletons.
{-# LANGUAGE DataKinds, KindSignatures, TypeFamilies, GADTs, TypeOperators,
ScopedTypeVariables, MultiParamTypeClasses, FlexibleInstances #-}
data Nat = Z | Inc Nat
data SNat :: Nat -> * where
SZ :: SNat Z
SInc :: NatSingleton n => SNat n -> SNat (Inc n)
class NatSingleton (a :: Nat) where
sing :: SNat a
instance NatSingleton Z where sing = SZ
instance NatSingleton a => NatSingleton (Inc a) where sing = SInc sing
type family Max (a :: Nat) (b :: Nat) :: Nat
type instance Max Z a = a
type instance Max a Z = a
type instance Max (Inc a) (Inc b) = Inc (Max a b)
data Term (l :: Nat) a where
Var :: a -> Term Z a
Abs :: NatSingleton l => a -> Term l a -> Term (Inc l) a
App :: (NatSingleton l1, NatSingleton l2)
=> Term l1 a -> Term l2 a -> Term (Max l1 l2) a
I :: Term Z a
K :: Term Z a
S :: Term Z a
fv :: Eq a => Term l a -> [a]
fv (Var v) = [v]
fv (Abs x e) = filter (/= x) $ fv e
fv (App e1 e2) = fv e1 ++ fv e2
fv _ = []
eliminateLambda :: (Eq a, NatSingleton l) => Term (Inc l) a -> Term l a
eliminateLambda t =
case t of
Abs x t ->
case t of
Var y
| y == x -> I
| otherwise -> App K (Var y)
Abs {} -> Abs x $ eliminateLambda t
App a b -> S `App` (eliminateLambda $ Abs x a)
`App` (eliminateLambda $ Abs x b)
App a b -> eliminateLambdaApp a b
eliminateLambdaApp
:: forall a l1 l2 l .
(Eq a, Max l1 l2 ~ Inc l,
NatSingleton l1,
NatSingleton l2)
=> Term l1 a -> Term l2 a -> Term l a
eliminateLambdaApp a b =
case (sing :: SNat l1, sing :: SNat l2) of
(SInc _, SZ ) -> App (eliminateLambda a) b
(SZ , SInc _) -> App a (eliminateLambda b)
(SInc _, SInc _) -> App (eliminateLambda a) (eliminateLambda b)
convert :: forall a l . Eq a => NatSingleton l => Term l a -> Term Z a
convert t =
case sing :: SNat l of
SZ -> t
SInc _ -> convert $ eliminateLambda t
The key insight is that S, K and I are just constant Lam terms, in the same way that 1, 2 and 3 are constant Ints. It would be pretty easy to make rule 5 type-check by making an inverse to the 'convert' function:
nvert :: SKI a -> Lam a
nvert S = Abs "x" (Abs "y" (Abs "z" (App (App (Var "x") (Var "z")) (App (Var "y") (Var "z")))))
nvert K = Abs "x" (Abs "y" (Var "x"))
nvert I = Abs "x" (Var "x")
nvert (V x) = Var x
nvert (x :# y) = App (nvert x) (nvert y)
Now we can use 'nvert' to make rule 5 type-check:
convert (Abs x (Abs y e)) | x `elem` fv e = convert (Abs x (nvert (convert (Abs y e))))
We can see that the left and the right are identical (we'll ignore the guard), except that 'Abs y e' on the left is replaced by 'nvert (convert (Abs y e))' on the right. Since 'convert' and 'nvert' are each others' inverse, we can always replace any Lam 'x' with 'nvert (convert x)' and likewise we can always replace any SKI 'x' with 'convert (nvert x)', so this is a valid equation.
Unfortunately, while it's a valid equation it's not a useful function definition because it won't cause the computation to progress: we'll just convert 'Abs y e' back and forth forever!
To break this loop we can replace the call to 'nvert' with a 'reminder' that we should do it later. We do this by adding a new constructor to Lam:
data Lam a = Var a -- v
| Abs a (Lam a) -- \v . e1
| App (Lam a) (Lam a) -- e1 e2
| Com (SKI a) -- Reminder to COMe back later and nvert
deriving (Eq, Show)
Now rule 5 uses this reminder instead of 'nvert':
convert (Abs x (Abs y e)) | x `elem` fv e = convert (Abs x (Com (convert (Abs y e))))
Now we need to make good our promise to come back, by making a separate rule to replace reminders with actual calls to 'nvert', like this:
convert (Com c) = convert (nvert c)
Now we can finally break the loop: we know that 'convert (nvert c)' is always identical to 'c', so we can replace the above line with this:
convert (Com c) = c
Notice that our final definition of 'convert' doesn't actually use 'nvert' at all! It's still a handy function though, since other functions involving Lam can use it to handle the new 'Com' case.
You've probably noticed that I've actually named this constructor 'Com' because it's just a wrapped-up COMbinator, but I thought it would be more informative to take a slightly longer route than just saying "wrap up your SKIs in Lams" :)
If you're wondering why I called that function "nvert", see http://unapologetic.wordpress.com/2007/05/31/duality-terminology/ :)
Warbo is right, combinators are constant lambda terms, consequently the conversion function is
T[ ]:L -> C with L the set of lambda terms and C that of combinatory terms and with C ⊂ L .
So there is no typing problem for the rule T[λx.λy.E] => T[λx.T[λy.E]]
Here an implementation in Scala.

Resources