[Haskell-cafe] Minim interpreter

Hugh Perkins hughperkins at gmail.com
Fri Jul 20 17:56:13 EDT 2007


Kindof vaguely made a start on this, but cant quite see how to handle
variables.

I guess variables can be stored as a (Map.Map String Double), at least for a
first draft?

Then, I'm building up two hierarchies in parallel:
- a set of parsec functions to parse the incoming string into a Program
hierarchy
- a set of data types to represent a program

Then, there's a class called "Eval" containing a function "eval" which is
instanced for each bit of the program hierarchy, so we simply call "eval" on
the top level, and the program is executed.

That works just fine as long as the only thing eval has to cope with is
print statements (so eval has type IO ()), but I'm guessing the clean
solution is to thread a Map.Map through that somehow?

Solution so far:

-- parsing hierarchy (pretty basic, but this bit doesnt seem particularly
scary)

string :: Parsec.Parser String
string = Parsec.many1 Parsec.letter

minimprint = do Parsec.string "print"
                Parsec.many1 (Parsec.char ' ')
                Parsec.char '"'
                stringvalue <- string
                Parsec.char '"'
                return (Print stringvalue)

-- program data type hierarchy

data Program = ProgramLeaf Statement | ProgramTree Program Statement
   deriving(Show)

data Statement = PrintStatement Print |
                 AssignmentStatement Assignment
   deriving(Show)

data Print = Print String
   deriving(Show)

data Assignment = VarAssignment Variable Value |
                  Increment Variable |
                  Decrement Variable
   deriving(Show)

data Variable = Variable String
   deriving(Show)

data Value = ValueFromConstant Constant | ValueFromVariable Variable
   deriving(Show)

newtype Constant = Constant Int
   deriving(Show)

-- eval instances

class Eval a where
   eval :: a -> IO()

instance Eval Program where
   eval (ProgramLeaf statement) = eval statement
   eval (ProgramTree program statement) = do eval program
                                             eval statement
instance Eval Statement where
   eval ( PrintStatement print) = eval print
   eval ( AssignmentStatement assignment) = return ()
instance Eval Print where
   eval (Print value) = putStrLn value

-- some code to test this
minimparse minimsentence = case (Parsec.runParser minimprint () ""
minimsentence) of
                                (Right statement) -> eval statement
                                Left error -> putStrLn("error: " ++
show(error))

test = minimparse "print \"hello\""


Running "test" correctly gives an output of "hello", which is a good start.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070720/76203b8e/attachment-0001.htm


More information about the Haskell-Cafe mailing list