tock-mirror/Main.hs
Adam Sampson 6047836456 Add a first shot at the assembly analyser, and make GenerateC use it.
This does about the minimum necessary for assembly analysis to work. It assumes
that any function it hasn't been able to analyse itself needs 512 bytes (most
need far less); it doesn't do any flow analysis; it doesn't do a lot of sanity
checking. However, it produces sensible numbers, and works with the demos I've
tried so far.

I was originally going to make this a separate tool, but there are a number of
bits of the code can be nicely reused, so it's a separate "operating mode" in
the existing program (as is parse-only mode now).
2007-08-08 19:39:47 +00:00

165 lines
4.3 KiB
Haskell

-- | Driver for the compiler.
module Main where
import Control.Monad
import Control.Monad.Error
import Control.Monad.State
import List
import System
import System.Console.GetOpt
import System.IO
import AnalyseAsm
import CompState
import Errors
import GenerateC
import GenerateCPPCSP
import Parse
import Pass
import PrettyShow
import SimplifyExprs
import SimplifyProcs
import SimplifyTypes
import Unnest
passes :: [(String, Pass)]
passes =
[ ("Simplify types", simplifyTypes)
, ("Simplify expressions", simplifyExprs)
, ("Simplify processes", simplifyProcs)
, ("Flatten nested declarations", unnest)
]
type OptFunc = CompState -> IO CompState
options :: [OptDescr OptFunc]
options =
[ Option [] ["mode"] (ReqArg optMode "MODE") "select mode (options: parse, compile, post-c)"
, Option ['v'] ["verbose"] (NoArg $ optVerbose) "be more verbose (use multiple times for more detail)"
, Option [] ["backend"] (ReqArg optBackend "BACKEND") "backend (options: CIF, CPPCSP)"
, Option ['o'] ["output"] (ReqArg optOutput "FILE") "output file (default \"-\")"
]
optMode :: String -> OptFunc
optMode s ps
= do mode <- case s of
"parse" -> return ModeParse
"compile" -> return ModeCompile
"post-c" -> return ModePostC
_ -> dieIO $ "Unknown mode: " ++ s
return $ ps { csMode = mode }
optVerbose :: OptFunc
optVerbose ps = return $ ps { csVerboseLevel = csVerboseLevel ps + 1 }
optOutput :: String -> OptFunc
optOutput s ps = return $ ps { csOutputFile = s }
optBackend :: String -> OptFunc
optBackend s ps = return $ ps { csBackend = s }
getOpts :: [String] -> IO ([OptFunc], [String])
getOpts argv =
case getOpt RequireOrder options argv of
(o,n,[] ) -> return (o,n)
(_,_,errs) -> error (concat errs ++ usageInfo header options)
where header = "Usage: tock [OPTION...] SOURCEFILE"
main :: IO ()
main = do
argv <- getArgs
(opts, args) <- getOpts argv
let fn = case args of
[fn] -> fn
_ -> error "Must specify a single input file"
initState <- foldl (>>=) (return emptyState) opts
let operation
= case csMode initState of
ModeParse -> compile fn
ModeCompile -> compile fn
ModePostC -> postCAnalyse fn
-- Run the compiler.
v <- evalStateT (runErrorT operation) initState
case v of
Left e -> dieIO e
Right r -> return ()
-- | Write the output to the file the user wanted.
writeOutput :: String -> PassM ()
writeOutput output
= do optsPS <- get
case csOutputFile optsPS of
"-" -> liftIO $ putStr output
file ->
do progress $ "Writing output file " ++ file
f <- liftIO $ openFile file WriteMode
liftIO $ hPutStr f output
liftIO $ hClose f
-- | Compile a file.
-- This is written in the PassM monad -- as are most of the things it calls --
-- because then it's very easy to pass the state around.
compile :: String -> PassM ()
compile fn
= do optsPS <- get
debug "{{{ Preprocess"
loadSource fn
debug "}}}"
debug "{{{ Parse"
progress "Parse"
ast1 <- parseProgram fn
debugAST ast1
debug "}}}"
showWarnings
output <-
case csMode optsPS of
ModeParse -> return $ show ast1
ModeCompile ->
do progress "Passes:"
ast2 <- (runPasses passes) ast1
debug "{{{ Generate Code"
c <-
case csBackend optsPS of
"CPPCSP" ->
do progress "Generate C++CSP"
c' <- generateCPPCSP ast2
return c'
"CIF" ->
do progress "Generate C/CIF"
c' <- generateC ast2
return c'
_ ->
do error ("Unknown backend: " ++ (csBackend optsPS))
debug "}}}"
return c
showWarnings
writeOutput output
progress "Done"
-- | Analyse an assembly file.
postCAnalyse :: String -> PassM ()
postCAnalyse fn
= do asm <- liftIO $ readSource fn
progress "Analysing assembly"
output <- analyseAsm asm
showWarnings
writeOutput output