Making a generic interpreter

Hi, I have made the following (very small and basic) interpter: data Code = PUSH Integer | ADD | BRANCH [Code] [Code] | CMP deriving (Show) data StackElement = StackInteger Integer | StackBool Bool deriving (Show) type Stack = [StackElement] eval :: [Code] -> Stack -> Stack eval [] s = s eval (PUSH n:t) s = eval t (StackInteger n:s) eval (ADD:t) (StackInteger x:StackInteger y:s) = eval t (StackInteger (x + y):s) eval (CMP:t) (StackInteger x:StackInteger y:s) = eval t (StackBool (x == y):s) eval (BRANCH c1 c2:t) (StackBool cond:s) = if cond then eval (c1 ++ t) s else eval (c2 ++ t) s Now, I would like to change StackElement to be able to work with any types, that is: data StackElement a b = StackInteger a | StackInteger b deriving (Show) How would I make this change? I thought about using typeclasses, but since type a and type b in StackElement a b clearly are related (the == operation on type a must result in type b), I need to use multi-parameter type classes (and maybe also functional dependecies?). I also thought about introducing a new type Operation: data Operation a b = Operation { cmp :: a -> a -> b, add :: a -> a -> a, (more required functions) } Is any of these solutions the preferred one, or is there another solution that I don't know of (this is very likely, I'm completely new to Haskell)? Thanks for taking your time and reading this lengthy post, Erik

Erik,
On Fri, May 6, 2011 at 3:01 AM, Erik Helin
Now, I would like to change StackElement to be able to work with any types, that is:
data StackElement a b = StackInteger a | StackInteger b deriving (Show)
How would I make this change?
I don't see how you can make the StackBool something else than Bool. The CMP and BRANCH operators seem to me very Boolean by definition. Can you provide an example of how it would work? Patrick
I thought about using typeclasses, but since type a and type b in StackElement a b clearly are related (the == operation on type a must result in type b), I need to use multi-parameter type classes (and maybe also functional dependecies?).
I also thought about introducing a new type Operation:
data Operation a b = Operation { cmp :: a -> a -> b, add :: a -> a -> a, (more required functions) }
Is any of these solutions the preferred one, or is there another solution that I don't know of (this is very likely, I'm completely new to Haskell)?
Thanks for taking your time and reading this lengthy post, Erik
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Hi Patrick,
thanks for taking your time!
On Fri, May 6, 2011 at 18:45, Patrick LeBoutillier
I don't see how you can make the StackBool something else than Bool. The CMP and BRANCH operators seem to me very Boolean by definition. Can you provide an example of how it would work?
Patrick
I actually can :) I've been hacking today, and the result is: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} class (Show a) => AbsInteger a b | a -> b where (+) :: a -> a -> a (==) :: a -> a -> b absInteger :: Integer -> a class (Show a) => AbsBool a where cond :: a -> [Code] -> [Code] -> [Code] absBool :: Bool -> a instance AbsBool Bool where cond b c1 c2 = if b then c1 else c2 absBool b = b instance AbsInteger Integer Bool where a + b = (Prelude.+) a b a == b = (Prelude.==) a b absInteger a = a Now, if I would like to use my own integer type or my own bool type, I can do: data MyInteger = MyInteger Integer deriving (Show) data MyBool = MyBool Bool deriving (Show) instance AbsBool MyBool where cond (MyBool b) c1 c2 = if b then c1 else c2 absBool b = MyBool b instance AbsInteger MyInteger MyBool where (MyInteger a) + (MyInteger b) = MyInteger $ (Prelude.+) a b (MyInteger a) + (MyInteger b) = MyBool $ (Prelude.==) a b absInteger a = MyInteger a The eval function has to be tweaked a little bit, but it is almost plug'n'play :) However, due to the functional dependency of AbsInteger, this does not allow me to use MyInteger and Bool, since there can only be one pair of an integer type and a bool type, and Integer and Bool are already instantiating AbsInteger . Do you know some of way of making it possible to have several integer type and boolean type pairs instantiating the class AbsInteger?

On Fri, May 06, 2011 at 07:39:13PM +0200, Erik Helin wrote:
Hi Patrick, thanks for taking your time!
On Fri, May 6, 2011 at 18:45, Patrick LeBoutillier
wrote: I don't see how you can make the StackBool something else than Bool. The CMP and BRANCH operators seem to me very Boolean by definition. Can you provide an example of how it would work?
Patrick
I actually can :) I've been hacking today, and the result is:
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-}
Why not use
class (Show a) => AbsInteger a where (+) :: a -> a -> a (==) :: AbsBool b => a -> a -> b absInteger :: Integer -> a
? -Brent

Erik,
On Fri, May 6, 2011 at 1:39 PM, Erik Helin
Hi Patrick, thanks for taking your time!
On Fri, May 6, 2011 at 18:45, Patrick LeBoutillier
wrote: I don't see how you can make the StackBool something else than Bool. The CMP and BRANCH operators seem to me very Boolean by definition. Can you provide an example of how it would work?
Patrick
I actually can :) I've been hacking today, and the result is:
Ok, now I get it! Did you try Brent's suggestion? For me it worked great and also allows you to drop the language extentions. Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Fri, May 6, 2011 at 20:01, Brent Yorgey
Why not use
class (Show a) => AbsInteger a where (+) :: a -> a -> a (==) :: AbsBool b => a -> a -> b absInteger :: Integer -> a
?
Because I believe (I might be very wrong now, I am very new to
Haskell) that I would run into problem with the b in "AbsBool b => a
-> a -> b" being unbounded when it would be used in:
data StackElement a b = StackInteger a
| StackBool b
deriving (Show)
eval :: (AbsInteger a, AbsNum b) => [Code] -> [StackElement a b] ->
[StackElement a b]
{- some cases omitted -}
eval (CMP:c) (StackInteger x:StackInteger y:t) = eval c (StackBool (x == y):t)
Now, GHC tells me that the type b returned by x == y does not need to
equal the b specified in the type definition of eval.
Did I do something wrong in my definiton of eval?
On Fri, May 6, 2011 at 21:12, Patrick LeBoutillier
Did you try Brent's suggestion? For me it worked great and also allows you to drop the language extentions.
I tried, but I didn't manage to get it working, due to the what I describe above. Could you post your code using Brent's suggestion? Clearly I am doing something wrong here, I just don't know what it is...

Erik,
Here's the code I came up with. One thing I changed was using the
names "add" and "eq" for the AbsInteger type class (I got confused by
all the =s and +s).
Coming from very imperative (and mostly dynamically typed) background
I must admit that this kind of stuff blows my mind a bit...
Patrick
==========================
data Code a = PUSH a | ADD | CMP
| BRANCH [Code a] [Code a]
deriving (Show)
data StackElement a b = StackValue a | StackBool b
deriving (Show)
type Stack a b = [StackElement a b]
class AbsInteger i where
add :: i -> i -> i
eq :: AbsBool b => i -> i -> b
absInteger :: Integer -> i
class AbsBool b where
cond :: (AbsInteger i) => b -> [Code i] -> [Code i] -> [Code i]
absBool :: Bool -> b
eval :: (AbsInteger a, AbsBool b) => [Code a] -> Stack a b -> Stack a b
eval [] s = s
eval (PUSH n:t) s = eval t (StackValue n:s)
eval (ADD:t) (StackValue x:StackValue y:s) = eval t (StackValue (x `add` y):s)
eval (CMP:t) (StackValue x:StackValue y:s) = eval t (StackBool (x `eq` y):s)
eval (BRANCH c1 c2:t) (StackBool b:s) = eval ((cond b c1 c2) ++ t) s
instance AbsBool Bool where
cond b c1 c2 = if b then c1 else c2
absBool b = b
instance AbsInteger Integer where
a `add` b = (+) a b
a `eq` b = absBool $ a == b
absInteger a = a
data MyInteger = MyInteger Integer deriving (Show)
data MyBool = MyBool Bool deriving (Show)
instance AbsBool MyBool where
cond (MyBool b) c1 c2 = if b then c1 else c2
absBool b = MyBool b
instance AbsInteger MyInteger where
(MyInteger a) `add` (MyInteger b) = MyInteger $ (+) a b
(MyInteger a) `eq` (MyInteger b) = absBool $ (==) a b
absInteger a = MyInteger a
code :: AbsInteger a => [Code a]
code = [PUSH . absInteger $ 1, PUSH . absInteger $ 2, ADD, PUSH .
absInteger $ 3, CMP, BRANCH [PUSH . absInteger $ 1] [PUSH . absInteger
$ 0]]
test1 = eval code [] :: Stack Integer Bool
test2 = eval code [] :: Stack Integer MyBool
test3 = eval code [] :: Stack MyInteger Bool
test4 = eval code [] :: Stack MyInteger MyBool
On Fri, May 6, 2011 at 3:32 PM, Erik Helin
On Fri, May 6, 2011 at 20:01, Brent Yorgey
wrote: Why not use
class (Show a) => AbsInteger a where (+) :: a -> a -> a (==) :: AbsBool b => a -> a -> b absInteger :: Integer -> a
?
Because I believe (I might be very wrong now, I am very new to Haskell) that I would run into problem with the b in "AbsBool b => a -> a -> b" being unbounded when it would be used in:
data StackElement a b = StackInteger a | StackBool b deriving (Show)
eval :: (AbsInteger a, AbsNum b) => [Code] -> [StackElement a b] -> [StackElement a b] {- some cases omitted -} eval (CMP:c) (StackInteger x:StackInteger y:t) = eval c (StackBool (x == y):t)
Now, GHC tells me that the type b returned by x == y does not need to equal the b specified in the type definition of eval.
Did I do something wrong in my definiton of eval?
On Fri, May 6, 2011 at 21:12, Patrick LeBoutillier
wrote: Did you try Brent's suggestion? For me it worked great and also allows you to drop the language extentions.
I tried, but I didn't manage to get it working, due to the what I describe above. Could you post your code using Brent's suggestion?
Clearly I am doing something wrong here, I just don't know what it is...
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Thank you Patrick for posting your code, it helps a lot too see a
complete example!
On Sat, May 7, 2011 at 03:11, Patrick LeBoutillier
instance AbsInteger Integer where a `add` b = (+) a b a `eq` b = absBool $ a == b absInteger a = a
In my code, I did not use "a `eq` b = absBool $ a == b". Instead, I used "a `eq` b = a == b". I thought, since "a == b" is of type Bool, and Bool is an instance of AbsBool, I can just return type Bool. Why isn't this the case? What is it about typeclasses that I'm not understanding? I updated my code to also use "absBool", and it works great without muti-parameter typeclasses and functional dependencies! Patrick and Brent, thank you so much for your help! You have both inspired me to continue my journey with Haskell :) Btw, Patrick, do you have any small Haskell project (or can you recommend some other project) on github (or something similar) that I can read to see more examples of good Haskell code?

On Saturday 07 May 2011 11:39:44, Erik Helin wrote:
Thank you Patrick for posting your code, it helps a lot too see a complete example!
On Sat, May 7, 2011 at 03:11, Patrick LeBoutillier
wrote: instance AbsInteger Integer where a `add` b = (+) a b a `eq` b = absBool $ a == b absInteger a = a
In my code, I did not use "a `eq` b = absBool $ a == b". Instead, I used "a `eq` b = a == b". I thought, since "a == b" is of type Bool, and Bool is an instance of AbsBool, I can just return type Bool.
Why isn't this the case? What is it about typeclasses that I'm not understanding?
A type signature foo :: (Bar b) => SomeType -> b says "given a value of SomeType, I can produce return values of *any* type, as long as it's an instance of Bar". The caller decides which type it wants and the callee must be able to produce it. In OO, on the other hand, the callee decides which type it returns, a signature Bar foo(SomeType s); (where Bar is an interface) says foo will return values of a type, all you know about which is that it implements Bar. Using explicit quantification, the Haskell type is foo :: forall b. (Bar b) => SomeType -> b while the OO-type would correspond to foo :: exists b. (Bar b) => SomeType -> b (the latter type doesn't exist in Haskell).
participants (4)
-
Brent Yorgey
-
Daniel Fischer
-
Erik Helin
-
Patrick LeBoutillier