[Haskell-beginners] Making a generic interpreter

Patrick LeBoutillier patrick.leboutillier at gmail.com
Sat May 7 03:11:04 CEST 2011


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 <erik.helin at gmail.com> wrote:
> On Fri, May 6, 2011 at 20:01, Brent Yorgey <byorgey at seas.upenn.edu> 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
> <patrick.leboutillier at gmail.com> 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



More information about the Beginners mailing list