summaryrefslogtreecommitdiff
path: root/Main.hs
blob: 20f479b7d1e0d8f6b3c5da122417cce1c82bee01 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
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, optFiles :: [FilePath] }

parseOptions :: Options -> [String] -> IO Options
parseOptions o []            = return o
parseOptions _ ("-h":_)      = usage >> exitSuccess
parseOptions o ("-ast":as)   = parseOptions (o { optAST = True }) as
parseOptions o ("-irpre":as) = parseOptions (o { optIRPre = True }) as
parseOptions o ("-ir":as)    = parseOptions (o { optIR = True }) as
parseOptions _ (('-':a):_)   = putStrLn ("Unknown option '" ++ a ++ "'") >> usage >> exitFailure
parseOptions o (f:as)        = parseOptions (o { optFiles = optFiles o ++ [f] }) as

main :: IO ()
main = do
    opts <- getArgs >>= parseOptions (Options False False False [])
    mfname <- case optFiles opts of
                  [] -> return Nothing
                  [fname] -> return (Just fname)
                  _ -> putStrLn "At most one filename argument expected" >> usage >> exitFailure
    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