module Main where import Control.Monad import System.Environment import System.Exit import Compiler import CompilerMacros import Optimiser import Parser import Stackify import VM usage :: IO () usage = do progname <- getProgName putStrLn $ "Usage: " ++ progname ++ " [-h] [-ast] [-ir] [filename.lisp]" putStrLn $ "When no filename is given, will read from stdin." putStrLn $ " -h Show this help" putStrLn $ " -ast Print AST after compiler macro's" putStrLn $ " -irpre Print IR after optimisation, before stackification" putStrLn $ " -ir Print IR after optimisation and stackification" data Options = Options { optAST :: Bool, optIRPre :: Bool, optIR :: Bool } -- TODO: clean this function up parseOptions' :: (Options, Maybe FilePath) -> [String] -> IO (Options, Maybe FilePath) parseOptions' pair [] = return pair parseOptions' _ ("-h":_) = usage >> exitSuccess parseOptions' (opt, fp) ("-ast":as) = parseOptions' (opt { optAST = True }, fp) as parseOptions' (opt, fp) ("-irpre":as) = parseOptions' (opt { optIRPre = True }, fp) as parseOptions' (opt, fp) ("-ir":as) = parseOptions' (opt { optIR = True }, fp) as parseOptions' _ (('-':a):_) = putStrLn ("Unknown option '" ++ a ++ "'") >> usage >> exitFailure parseOptions' (opt, Nothing) (f:as) = parseOptions' (opt, Just f) as parseOptions' (_, Just _) (_:_) = putStrLn "At most one filename argument expected" >> usage >> exitFailure parseOptions :: [String] -> IO (Options, Maybe FilePath) parseOptions = parseOptions' (Options False False False, Nothing) main :: IO () main = do (opts, mfname) <- getArgs >>= parseOptions source <- maybe getContents readFile mfname prog <- parseProgram mfname source >>= either (die . show) return let prog' = compilerMacros prog when (optAST opts) $ print prog' irprog <- either die return (compileProgram prog') let opt = optimise irprog when (optIRPre opts) $ print opt let optS = stackify opt when (optIR opts) $ print optS -- TODO: do we want to run the optimiser again now? In a situation as -- follows, stuff might be inlined still: -- t2 <- assign t1 -- push [t2] ; could've been push [t1] -- callc ... -- pop [t2] -- ... use t2 again ... -- TODO: this raises the question of using liveness for optimisation. -- In the example above, the pop instruction writes to t2, breaking up -- its lifetime, so that the assignment becomes dead. The current -- optimiser would not be able to catch this. vmRun optS