Error: "No instances for (x)..." - haskell

Exercise 14.16-17 in Thompson asks me to add the operations of multiplication and (integer) division to the type Expr, which represents a simple language for arithmetic, then define the functions show and eval (evaluates an expression of type Expr) for Expr.
My solution works for each arithmetic operation except division:
data Expr = L Int
| Expr :+ Expr
| Expr :- Expr
| Expr :* Expr
| Expr :/ Expr
instance Num Expr where
(L x) + (L y) = L (x + y)
(L x) - (L y) = L (x - y)
(L x) * (L y) = L (x * y)
instance Eq Expr where
(L x) == (L y) = x == y
instance Show Expr where
show (L n) = show n
show (e1 :+ e2) = "(" ++ show e1 ++ " + " ++ show e2 ++ ")"
show (e1 :- e2) = "(" ++ show e1 ++ " - " ++ show e2 ++ ")"
show (e1 :* e2) = "(" ++ show e1 ++ " * " ++ show e2 ++ ")"
show (e1 :/ e2) = "(" ++ show e1 ++ " / " ++ show e2 ++ ")"
eval :: Expr -> Expr
eval (L n) = L n
eval (e1 :+ e2) = eval e1 + eval e2
eval (e1 :- e2) = eval e1 - eval e2
eval (e1 :* e2) = eval e1 * eval e2
E.g.,
*Main> (L 6 :+ L 7) :- L 4
((6 + 7) - 4)
*Main> it :* L 9
(((6 + 7) - 4) * 9)
*Main> eval it
81
it :: Expr
However, I am running into problems when I try to implement division. I don't understand the error message I receive when I try to compile the following:
instance Integral Expr where
(L x) `div` (L y) = L (x `div` y)
eval (e1 :/ e2) = eval e1 `div` eval e2
This is the error:
Chapter 14.15-27.hs:19:9:
No instances for (Enum Expr, Real Expr)
arising from the superclasses of an instance declaration
at Chapter 14.15-27.hs:19:9-21
Possible fix:
add an instance declaration for (Enum Expr, Real Expr)
In the instance declaration for `Integral Expr'
In the first place, I have no idea why defining div for the data type Expr requires me to define an instance of Enum Expr or Real Expr.

Well, that's the way the Integral typeclass is defined. For information, you can e.g. just type :i Integral into GHCi.
You'll get
class (Real a, Enum a) => Integral a where ...
which means any type a that should be Integral has to be Real and Enum first. C'est la vie.
Note that maybe you've got your types messed up quite a bit. Take a look at
instance Num Expr where
(L x) + (L y) = L (x + y)
(L x) - (L y) = L (x - y)
(L x) * (L y) = L (x * y)
This just allows you to add Expressions if they wrap plain numbers. I'm pretty sure you don't want that.
You want to add arbitrary expressions and you already have a syntax for this. It's just
instance Num Expr where
(+) = (:+)
(-) = (:-)
-- ...
This allows you to write (L 1) + (L 2) with perfectly normal syntax. Likewise, eval should not just reduce expressions but yield a number, and therefore have the type eval :: Expr -> Integer. Division is simple for that matter
eval (a :/ b) = (eval a) `div` (eval b)
which is defined since you just divide numbers.

Related

Minimize parenthesis when printing expression

I have a simple arithmetic expression data structure that I want to be able to print. For sake of simplicity here I have made an example with 3 binary operations, addition, multiplication and division. The definition looks like this:
module ExprPrint where
import Text.Printf
data Expr = Lit Int
| Add Expr Expr
| Mul Expr Expr
| Div Expr Expr
instance Show Expr where
show (Lit x) = show x
show (Add e1 e2) = printf "(%s) + (%s)" (show e1) (show e2)
show (Mul e1 e2) = printf "(%s) * (%s)" (show e1) (show e2)
show (Div e1 e2) = printf "(%s) / (%s)" (show e1) (show e2)
The goal I have is to print the data structure while removing all superfluous parenthesis. of course the naive show function I have implemented above includes way too many of them. So what I want to do is make the Show instance take the precedence (Div and Mul over Add) and associativity(Add and Mul are associative while Div is left-associative) of the operations into account.
Here are some examples:
one = Lit 1
-- Shows "((1) + (1)) + (1)" but should be 1 + 1 + 1
addAssoc = show $ Add (Add one one) one
-- Shows "((1) * (1)) * (1)" but should be 1 * 1 * 1
mulAssoc = show $ Mul (Mul one one) one
-- Shows "((1) / (1)) / (1)" but should be 1 / 1 / 1
divAssoc = show $ Div (Div one one) one
-- Shows "(1) / ((1) / (1)) but should be 1 / (1 / 1)
divAssoc2 = show $ Div one (Div one one)
-- Show "((1) * (1)) + (1)" but should 1 * 1 + 1
addPrec = show $ Add (Mul one one) one
-- Show "(1) + ((1) * (1))" but should show 1 + (1 * 1)
addPrec2 = show $ Add one (Mul one one)
Is there an "easy" to take that into account in the show instance? I think I could do it by taking all the cases into account but that would be an explosion of functions. Is there some algorithm or known way to handle this?
I hope somebody has some pointers!
Thanks.
An instance in terms of show isn't powerful enough to avoid redundant parentheses, since it doesn't have any information about precedence available. You'll need to write your instance in terms of showsPrec instead, which does, like this:
module ExprPrint where
import Text.Show
data Expr = Lit Int
| Add Expr Expr
| Mul Expr Expr
| Div Expr Expr
instance Show Expr where
showsPrec prec (Lit x) = showsPrec prec x
showsPrec prec (Add e1 e2) = showParen (prec >= 7) $ showsPrec 7 e1 . showString " + " . showsPrec 7 e2
showsPrec prec (Mul e1 e2) = showParen (prec >= 8) $ showsPrec 8 e1 . showString " * " . showsPrec 8 e2
showsPrec prec (Div e1 e2) = showParen (prec >= 8) $ showsPrec 8 e1 . showString " / " . showsPrec 8 e2
I chose 6 and 7 for your precedence levels since that's what Haskell uses for its own +, *, and div operators, but it should be obvious how you'd choose different ones.
As for associativity, there's no perfect way to do that in general, but you can fake it with some precedence tweaks in your case, since math doesn't have any operators at the same precedence levels with different associativies. Here's an example of how to do that (I added Exp, with precendence level 8, to give an example of the right-associative way to do it too):
module ExprPrint where
import Text.Show
data Expr = Lit Int
| Add Expr Expr
| Mul Expr Expr
| Div Expr Expr
| Exp Expr Expr
instance Show Expr where
showsPrec prec (Lit x) = showsPrec prec x
showsPrec prec (Add e1 e2) = showParen (prec >= 7) $ showsPrec 6 e1 . showString " + " . showsPrec 7 e2
showsPrec prec (Mul e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " * " . showsPrec 8 e2
showsPrec prec (Div e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " / " . showsPrec 8 e2
showsPrec prec (Exp e1 e2) = showParen (prec >= 9) $ showsPrec 9 e1 . showString " ^ " . showsPrec 8 e2
That's still not perfect, since it still doesn't know the associative property of Add or Mul, so Mul one (Mul one one) will show as 1 * (1 * 1) instead of 1 * 1 * 1, but I don't think there's any possible way to fix that, since division doesn't share that property, but since it has the same precedence as multiplication, you can't distinguish them in showsPrec.
Actually, you can cheat a bit more than that, by peeking at the next level down and re-associating:
module ExprPrint where
import Text.Show
data Expr = Lit Int
| Add Expr Expr
| Mul Expr Expr
| Div Expr Expr
| Exp Expr Expr
instance Show Expr where
showsPrec prec (Lit x) = showsPrec prec x
showsPrec prec (Add e1 (Add e2 e3)) = showsPrec prec (Add (Add e1 e2) e3)
showsPrec prec (Add e1 e2) = showParen (prec >= 7) $ showsPrec 6 e1 . showString " + " . showsPrec 7 e2
showsPrec prec (Mul e1 (Mul e2 e3)) = showsPrec prec (Mul (Mul e1 e2) e3)
showsPrec prec (Mul e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " * " . showsPrec 8 e2
showsPrec prec (Div e1 e2) = showParen (prec >= 8) $ showsPrec 7 e1 . showString " / " . showsPrec 8 e2
showsPrec prec (Exp e1 e2) = showParen (prec >= 9) $ showsPrec 9 e1 . showString " ^ " . showsPrec 8 e2
I think this is perfect. All of your test cases pass now.

Haskell - Pattern matching with data types

I have a data type and function like this:
data Expr = Num Int | Add Expr Expr | Mult Expr Expr | Neg Expr | If Expr Expr Expr deriving (Show, Read)
prettyPrint :: Expr -> IO ()
prettyPrint expr = prettyPrint' expr 0
prettyPrint' :: Expr -> Int -> IO ()
prettyPrint' (Num x) i = putStrLn $ concat (replicate i " ") ++ "Num " ++ show x
prettyPrint' (Add x y) i = do
putStrLn $ concat (replicate i " ") ++ "Add"
prettyPrint' x (i+1)
prettyPrint' y (i+1)
prettyPrint' (Mult x y) i = do
putStrLn $ concat (replicate i " ") ++ "Mult"
prettyPrint' x (i+1)
prettyPrint' y (i+1)
prettyPrint' (Neg x) i = do
putStrLn $ concat (replicate i " ") ++ "Neg"
prettyPrint' x (i+1)
prettyPrint' (If x y z) i = do
putStrLn $ concat (replicate i " ") ++ "If"
prettyPrint' x (i+1)
prettyPrint' y (i+1)
prettyPrint' z (i+1)
In the function I am using pattern matching. The problem is that their is a lot of reuse of code. For example, the case for Mult and Add is basically the same code. Same goes for Num and Neg. Is there a way to write this based on how many variables the expression have? Like one for Num and Neg, since they have only one variable. One case for Mult and Add, since they have two variables. And a last case for If, since that expression have three variables.
NOTE:
I landed on this answer, I think it's a better solution than I started with:
prettyPrint :: Expr -> IO ()
prettyPrint expr = putStrLn (prettyPrint' 1 expr)
prettyPrint' :: Int -> Expr -> String
prettyPrint' i (Num x) = "Num " ++ show x
prettyPrint' i expr =
let indent x = concat (replicate i " ") ++ x
(op, args) = case expr of
Add x y -> ("Add", [x,y])
Mult x y -> ("Mult", [x,y])
Neg x -> ("Neg", [x])
If x y z -> ("If", [x,y,z])
in intercalate "\n" (op : map (indent . prettyPrint' (i + 1)) args)
First, I would stay out of the IO monad for as long as possible. Have prettyPrint' return a string to be printed.
prettyPrint :: Expr -> IO ()
prettyPrint = putStrLn . prettyPrint'
Now, the only job of prettyPrint' is to create a (possibly multiline) string to be printed. For numbers, that's easy: just use the show instance.
prettyPrint' :: Expr -> String
prettyPrint' e#(Num _) = show e
-- or, ignoring the Show instance for Expr altogether
-- prettyPrint' (Num x) = "Num " ++ show x
For the rest, there is a pattern:
Identify the constructor
Identify its arguments
Join the constructor name and its pretty-printed arguments with newlines. Each argument will be indented one level relative to its operator; the recursion will take care of multiple levels of indentation.
That will look like
prettyPrint' expr = let indent x = " " ++ x
(op, args) = case expr of
Add x y -> ("Add", [x,y])
Mult x y -> ("Mult", [x,y])
Neg x -> ("Neg", [x])
If x y z -> ("If", [x,y,z])
in intercalate "\n" (op : map (indent . prettyPrint') args)
As an example, consider what prettyPrint' will do with the expression Add (Num 3) (Num 5). First, it sets op to "Add" and args to [Num 3, Num 5]. Next, it maps indent . prettyPrint' over the argument list, to get [" Num 3", " Num 5"]. Putting the operator on the front of the list yields ["Add", " Num 3", " Num 3"], then joining them with intercalate produces "Add\n Num 3\n Num 5".
The only remaining boilerplate is in the case expression. I think it's possible to eliminate that, but it requires a level of generic programming I'm not familiar with. I'm sure someone else could probably run with my answer to fix that.
In general, when addressing duplication in code, it pays to keep the rule of three in mind. Two occurrences of a block of code isn't necessarily a problem.
That said, Haskell is a (very) strongly-typed language, so you generally can't pattern-match on arity like you can in, say, Erlang or Clojure.
If you really want to abstract away the recursion part of a recursive data structure, you can define the catamorphism for it. People often also call this a fold, so let's keep that slightly more friendly name:
data Expr =
Num Int | Add Expr Expr | Mult Expr Expr | Neg Expr | If Bool Expr Expr deriving (Show, Read)
foldExpr ::
(Int -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (Bool -> a -> a -> a) -> Expr -> a
foldExpr num _ _ _ _ (Num x) = num x
foldExpr num add mul neg iff (Add x y) =
add (foldExpr num add mul neg iff x) (foldExpr num add mul neg iff y)
foldExpr num add mul neg iff (Mult x y) =
mul (foldExpr num add mul neg iff x) (foldExpr num add mul neg iff y)
foldExpr num add mul neg iff (Neg x) = neg (foldExpr num add mul neg iff x)
foldExpr num add mul neg iff (If b x y) =
iff b (foldExpr num add mul neg iff x) (foldExpr num add mul neg iff y)
This is an entirely generic function that enables you turn turn any Expr value into any value of the type a, without worrying about reimplementing recursion every time. You just have to supply functions that deal with each of the cases.
You can, for example, easily write an evaluator:
evaluate :: Expr -> Int
evaluate = foldExpr id (+) (*) negate (\p x y -> if p then x else y)
(Notice, BTW, that I changed the definition of If, because I couldn't see how the OP definition would work.)
You can also write a function to turn an Expr value into a string, although this one is just a sketch; it needs indentation or bracket logic to work correctly:
prettyPrint :: Expr -> String
prettyPrint =
foldExpr
show -- Num
(\x y -> x ++ "+" ++ y) -- Add
(\x y -> x ++ "*" ++ y) -- Mult
(\x -> "(-" ++ x ++ ")") -- Neg
(\p x y -> "if " ++ show p ++ " then " ++ x ++ " else " ++ y) -- If
You can try it out in GHCi:
*Q53284410> evaluate (Num 42)
42
*Q53284410> evaluate (Add (Num 40) (Num 2))
42
*Q53284410> evaluate (Add (Mult (Num 4) (Num 10)) (Num 2))
42
*Q53284410> prettyPrint $ Num 42
"42"
*Q53284410> prettyPrint $ Mult (Num 6) (Num 7)
"6*7"
*Q53284410> prettyPrint $ Add (Mult (Num 2) (Num 3)) (Num 7)
"2*3+7"
Yes, just create a function to print list of Expr:
import Control.Monad (forM_)
printExprList::[Expr]->Int->String->IO ()
printExprList exprs i desc = do
putStrLn $ concat (replicate i " ") ++ desc
forM_ (zip exprs [i..]) $ \(e, j)-> prettyPrint' e (j+1)
and then call it to print:
prettyPrint' :: Expr -> Int -> IO ()
prettyPrint' (Add x y) i = printExprList [x, y] i "Add"
prettyPrint' (Mult x y) i = printExprList [x, y] i "Mult"
prettyPrint' (Neg x) i = printExprList [x] i "Neg"
prettyPrint' (If x y z) i = printExprList [x, y, z] i "If"
prettyPrint' (Num x) i = putStrLn $ concat (replicate i " ")
++ "Num " ++ show x

How can I make a function implement the internals of a custom instance of Show. Haskell

I wrote this data type:
data Poly = Lit Integer |
Var |
Add Poly Poly |
Mul Poly Poly
I'd like to also write a function printPoly for it, that takes a Poly expression and returns it converted to string. This can be implemented by just creating a custom instance of show for data type Poly like so:
instance Show Poly where
show (Lit x) = show x
show (Var) = "x"
show (Add x y) = (show x) ++ " + " ++ (show y)
show (Mul x y) = (show x) ++ "*" ++ (show y)
Now if I pass an expression like
main = do
print (Add (Lit 1) $ Add (Var) $ Mul (Var) $ Mul Var Var)
It returns 1 + x + x*x*x. Which is what I want. However, I want this done from a function printPoly, like so:
printPoly::Poly->String
printPoly (Lit x) = show x
printPoly (Var) = "x"
printPoly (Add x y) = (show x) ++ " + " ++ (show y)
printPoly (Mul x y) = (show x) ++ "*" ++ (show y)
Where am I wrong in the way I wrote this function?
To answer your question as-asked, this is what you want to do.
printPoly :: Poly -> String
printPoly (Lit x) = show x
printPoly (Var) = "x"
printPoly (Add x y) = (printPoly x) ++ " + " ++ (printPoly y)
printPoly (Mul x y) = (printPoly x) ++ "*" ++ (printPoly y)
instance Show Poly where
show = printPoly
However, this has some obvious problems. Consider print (Mul (Lit 2) $ Add Var Var). This would print 2*x + x, which when following precedence rules is clearly not what was intended.
printPoly :: Poly -> String
printPoly (Lit x) = show x
printPoly (Var) = "x"
printPoly (Add x y) = (b x $ printPoly x) ++ " + " ++ (b y $ printPoly y)
where b (Add _ _) p = "(" ++ p ++ ")"
b _ p = p
printPoly (Mul x y) = (b x $ printPoly x) ++ " * " ++ (b y $ printPoly y)
where b (Mul _ _) p = "(" ++ p ++ ")"
b _ p = p
This will print out 2 * (x + x) which is the correct interpretation of the given AST. Further, you could simplify the whole thing a bit by using printf from Text.Printf
printPoly :: Poly -> String
printPoly (Lit x) = show x
printPoly (Var) = "x"
printPoly (Add x y) = printf "%s + %s" (b x $ printPoly x) (b y $ printPoly y)
where b (Add _ _) = printf "(%s)"
b _ = id
printPoly (Mul x y) = printf "%s * %s" (b x $ printPoly x) (b y $ printPoly y)
where b (Mul _ _) = printf "(%s)"
b _ = id
Of course, this is still doing a lot of linked-list traversal, munging together strings so it won't be very fast, but at least it's correct ;)

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.

Count number of operators in an expression - Cannot infer instance

I'm working on a function that can count the number of operators used in an expression. My code is as follows:
data Expr = Lit Int |
Expr :+: Expr |
Expr :-: Expr
size :: Expr -> Int
size (Lit n) = 0
size (e1 :+: e2) = 1 + (size e1) + (size e2)
size (e1 :-: e2) = 1 + (size e1) + (size e2)
But when I try to execute this code using Hugs98 i get the following error:
Main> size 2+3
ERROR - Cannot infer instance
*** Instance : Num Expr
*** Expression : size 2 + 3
Can somebody tell me what I'm doing wrong? I'm really out of idea's myself.
2+3 is not a valid expression. With your types, primtive values are created using the Lit data constructor, and the valid operators are :+: and :-:. So what you really need is Lit 2 :+: Lit 3. So try
size (Lit 2 :+: Lit 3)
You can make it a Num instance:
instance Num Expr where
(+) = (:+:)
(-) = (:-:)
negate = (0 -)
fromInteger = Lit . fromInteger
(*) = error "not implemented"
abs = error "not implemented"
signum = error "not implemented"
Once that is in place, size (2+3) will work (note the parenthesis).

Resources