Nicer option parsing, and a -o option to write output to a file

This commit is contained in:
Adam Sampson 2007-04-25 16:07:12 +00:00
parent e64fa81f83
commit dd991a5587
5 changed files with 48 additions and 32 deletions

View File

@ -22,14 +22,26 @@ passes =
, ("Flatten nested declarations", unnest) , ("Flatten nested declarations", unnest)
] ]
options :: [OptDescr Flag] type OptFunc = ParseState -> IO ParseState
options :: [OptDescr OptFunc]
options = options =
[ Option [] ["parse-only"] (NoArg ParseOnly) "only parse input file" [ Option [] ["parse-only"] (NoArg optParseOnly) "only parse input file"
, Option ['v'] ["verbose"] (NoArg Verbose) "show progress information" , Option ['v'] ["verbose"] (NoArg $ optVerboseLevel 1) "show progress information"
, Option [] ["debug"] (NoArg Debug) "show detailed information for debugging" , Option [] ["debug"] (NoArg $ optVerboseLevel 2) "show detailed information for debugging"
, Option ['o'] ["output"] (ReqArg optOutput "FILE") "output file (default \"-\")"
] ]
getOpts :: [String] -> IO ([Flag], [String]) optParseOnly :: OptFunc
optParseOnly ps = return $ ps { psParseOnly = True }
optVerboseLevel :: Int -> OptFunc
optVerboseLevel n ps = return $ ps { psVerboseLevel = max (psVerboseLevel ps) n }
optOutput :: String -> OptFunc
optOutput s ps = return $ ps { psOutputFile = s }
getOpts :: [String] -> IO ([OptFunc], [String])
getOpts argv = getOpts argv =
case getOpt RequireOrder options argv of case getOpt RequireOrder options argv of
(o,n,[] ) -> return (o,n) (o,n,[] ) -> return (o,n)
@ -48,11 +60,7 @@ main = do
[fn] -> fn [fn] -> fn
_ -> error "Must specify a single input file" _ -> error "Must specify a single input file"
let state0 = emptyState { psFlags = opts } state0 <- foldl (>>=) (return emptyState) opts
progressIO state0 $ "Options: " ++ show opts
progressIO state0 $ "Compiling " ++ fn
progressIO state0 ""
debugIO state0 "{{{ Preprocess" debugIO state0 "{{{ Preprocess"
state0a <- loadSource fn state0 state0a <- loadSource fn state0
@ -64,7 +72,7 @@ main = do
debugASTIO state1 ast1 debugASTIO state1 ast1
debugIO state1 "}}}" debugIO state1 "}}}"
if ParseOnly `elem` opts then if psParseOnly state1 then
putStrLn $ show ast1 putStrLn $ show ast1
else do else do
progressIO state1 "Passes:" progressIO state1 "Passes:"
@ -73,7 +81,13 @@ main = do
debugIO state2 "{{{ Generate C" debugIO state2 "{{{ Generate C"
progressIO state2 "Generate C" progressIO state2 "Generate C"
c <- generateC state2 ast2 c <- generateC state2 ast2
putStr c case psOutputFile state2 of
"-" -> putStr c
file ->
do progressIO state2 $ "Writing output file " ++ file
f <- openFile file WriteMode
hPutStr f c
hClose f
debugIO state2 "}}}" debugIO state2 "}}}"
progressIO state2 "Done" progressIO state2 "Done"

View File

@ -27,7 +27,7 @@ $(targets): $(sources)
CFLAGS = -g -std=gnu99 -Wall `kroc --cflags` `kroc --ccincpath` CFLAGS = -g -std=gnu99 -Wall `kroc --cflags` `kroc --ccincpath`
%.fco.c: %.occ fco %.fco.c: %.occ fco
./fco -v $< >$@ || ( rm -f $@; exit 1 ) ./fco -v -o $@ $<
indent -kr -pcs $@ indent -kr -pcs $@
%.fco: %.fco.o fco_support.h kroc-wrapper-c.o kroc-wrapper.occ %.fco: %.fco.o fco_support.h kroc-wrapper-c.o kroc-wrapper.occ

View File

@ -8,13 +8,12 @@ import qualified AST as A
import Errors import Errors
import Metadata import Metadata
data Flag = ParseOnly | Verbose | Debug
deriving (Eq, Show, Data, Typeable)
-- | State necessary for compilation. -- | State necessary for compilation.
data ParseState = ParseState { data ParseState = ParseState {
-- Set by Main -- Set by Main (from command-line options)
psFlags :: [Flag], psVerboseLevel :: Int,
psParseOnly :: Bool,
psOutputFile :: String,
-- Set by preprocessor -- Set by preprocessor
psSourceFiles :: [(String, String)], psSourceFiles :: [(String, String)],
@ -41,7 +40,9 @@ instance Show (A.Process -> A.Process) where
emptyState :: ParseState emptyState :: ParseState
emptyState = ParseState { emptyState = ParseState {
psFlags = [], psVerboseLevel = 0,
psParseOnly = False,
psOutputFile = "-",
psSourceFiles = [], psSourceFiles = [],

View File

@ -38,25 +38,29 @@ runPasses ((s, p):ps) ast
debug $ "}}}" debug $ "}}}"
runPasses ps ast' runPasses ps ast'
verboseMessage :: Int -> String -> PassM ()
verboseMessage n s
= do ps <- get
liftIO $ verboseMessageIO n ps s
verboseMessageIO :: Int -> ParseState -> String -> IO ()
verboseMessageIO n ps s = when (psVerboseLevel ps >= n) $ hPutStrLn stderr s
-- | Print a progress message if appropriate. -- | Print a progress message if appropriate.
progress :: String -> PassM () progress :: String -> PassM ()
progress s progress = verboseMessage 1
= do ps <- get
liftIO $ progressIO ps s
-- | Print a progress message if appropriate (in the IO monad). -- | Print a progress message if appropriate (in the IO monad).
progressIO :: ParseState -> String -> IO () progressIO :: ParseState -> String -> IO ()
progressIO ps s = when (Verbose `elem` psFlags ps) $ hPutStrLn stderr s progressIO = verboseMessageIO 1
-- | Print a debugging message if appropriate. -- | Print a debugging message if appropriate.
debug :: String -> PassM () debug :: String -> PassM ()
debug s debug = verboseMessage 2
= do ps <- get
liftIO $ debugIO ps s
-- | Print a debugging message if appropriate (in the IO monad). -- | Print a debugging message if appropriate (in the IO monad).
debugIO :: ParseState -> String -> IO () debugIO :: ParseState -> String -> IO ()
debugIO ps s = when (Debug `elem` psFlags ps) $ hPutStrLn stderr s debugIO = verboseMessageIO 2
-- | Dump the AST and parse state if appropriate. -- | Dump the AST and parse state if appropriate.
debugAST :: A.Process -> PassM () debugAST :: A.Process -> PassM ()

View File

@ -23,8 +23,6 @@ Types needs cleaning up and Haddocking.
Add an option for whether to compile out overflow/bounds checks. Add an option for whether to compile out overflow/bounds checks.
Add a -o option to control where the output goes (stdout by default for now).
## Parser ## Parser
The indentation parser is way too simplistic. The indentation parser is way too simplistic.
@ -37,6 +35,8 @@ Record literals aren't implemented.
Expression simplification -- this should use generics, so that we can have a Expression simplification -- this should use generics, so that we can have a
default behaviour that simplifies expressions inside another one. default behaviour that simplifies expressions inside another one.
(More generally, simplifyExpressions should really be split into a simplifier
and a constant-finder -- or should return two values.)
Output item expressions should be pulled up to variables. Output item expressions should be pulled up to variables.
@ -73,9 +73,6 @@ to be a bad idea for very large counts (since I assume it'll allocate off the
stack). We should probably do a malloc if it's not determinable at compile stack). We should probably do a malloc if it's not determinable at compile
time. time.
The operator functions need to have the type name attached -- they'll only work
for INT at the moment.
Real-to-integer conversions don't work correctly. Real-to-integer conversions don't work correctly.
## Long-term ## Long-term