]> ruin.nu Git - proglang.git/blob - Interpreter.hs
interpreter compiles
[proglang.git] / Interpreter.hs
1 -- automatically generated by BNF Converter
2 module Main where
3
4
5 import IO ( stdin, hGetContents )
6 import System ( getArgs, getProgName )
7
8 import Lexsyntax
9 import Parsyntax
10 import Skelsyntax
11 import Printsyntax
12 import Abssyntax
13
14 import Typecheck
15 import Interpret
16 import Control.Monad.State hiding (State)
17 import Data.Map as Map hiding (showTree)
18
19 import ErrM
20
21 type ParseFun a = [Token] -> Err a
22
23 myLLexer = myLexer
24
25 type Verbosity = Int
26
27 splitFunStm :: [FuncStm] -> ([Func],[Stm])
28 splitFunStm [] = ([],[])
29 splitFunStm ((F f):fss) = let (fs,ss) = splitFunStm fss in (f:fs,ss)
30 splitFunStm ((S s):fss) = let (fs,ss) = splitFunStm fss in (fs,s:ss)
31
32 putStrV :: Verbosity -> String -> IO ()
33 putStrV v s = if v > 1 then putStrLn s else return ()
34
35 runFile :: Verbosity -> ParseFun Program -> FilePath -> IO ()
36 runFile v p f = putStrLn f >> readFile f >>= run v p
37
38 run :: Verbosity -> ParseFun Program -> String -> IO ()
39 run v p s = let ts = myLLexer s in case p ts of
40         Bad s    -> do
41                 putStrLn "\nParse              Failed...\n"
42                 putStrV v "Tokens:"
43                 putStrV v $ show ts
44                 putStrLn s
45         Ok (Program s) -> let (fun,st) = splitFunStm (s) in do
46                 putStrLn "\nParse Successful!"
47                 showTree v (Program s)
48                 runStateT (do mapM Typecheck.addFunction fun; mapM typeCheckFunction fun; mapM typeCheckStm st) Typecheck.emptyState
49                 print "The program is type-correct!!"
50                 print "Running program:"
51                 runStateT (do mapM Interpret.addFunction fun; mapM execute st) Interpret.emptyState
52                 print "Done running program!"
53                 return ()
54
55 showTree :: (Show a, Print a) => Int -> a -> IO ()
56 showTree v tree
57  = do
58       putStrV v $ "\n[Abstract Syntax]\n\n" ++ show tree
59       putStrV v $ "\n[Linearized tree]\n\n" ++ printTree tree
60
61 main :: IO ()
62 main = do args <- getArgs
63           case args of
64             [] -> hGetContents stdin >>= run 2 pProgram
65             "-s":fs -> mapM_ (runFile 0 pProgram) fs
66             fs -> mapM_ (runFile 2 pProgram) fs
67
68
69
70
71