aboutsummaryrefslogtreecommitdiff
path: root/app/Main.hs
diff options
context:
space:
mode:
authorJuan J. Martinez <jjm@usebox.net>2022-09-07 16:26:50 +0100
committerJuan J. Martinez <jjm@usebox.net>2022-09-07 16:26:50 +0100
commit65c8beecb14f6d09c49504d74beedd58cc7ddd17 (patch)
tree0a39cc6fc3f78153272c6528300936c039351d3e /app/Main.hs
parent48896c56c39344fa429260d3969eccc93ef8035c (diff)
downloadmicro-lang-hs-65c8beecb14f6d09c49504d74beedd58cc7ddd17.tar.gz
micro-lang-hs-65c8beecb14f6d09c49504d74beedd58cc7ddd17.zip
Better project layout, removed warnings
Diffstat (limited to 'app/Main.hs')
-rw-r--r--app/Main.hs92
1 files changed, 92 insertions, 0 deletions
diff --git a/app/Main.hs b/app/Main.hs
new file mode 100644
index 0000000..5a16129
--- /dev/null
+++ b/app/Main.hs
@@ -0,0 +1,92 @@
+module Main where
+
+import Control.Monad (when)
+import Control.Monad.State (evalState)
+import qualified Data.Map as Map
+import Data.Maybe (fromMaybe)
+import Micro.Compiler
+import Micro.Error (showErrorList, showParserError)
+import Micro.Lexer (scan)
+import Micro.Parser (parse, parseFromFile)
+import System.Console.GetOpt
+import System.Environment (getProgName)
+import System.Environment.Blank (getArgs)
+import System.Exit (exitFailure, exitSuccess)
+import System.IO (hPutStr, hPutStrLn, stderr, stdout)
+
+version = "0.1.0"
+
+data Options = Options
+ { optParse :: Bool,
+ optHelp :: Bool,
+ optVersion :: Bool
+ }
+
+defOptions =
+ Options
+ { optParse = False,
+ optHelp = False,
+ optVersion = False
+ }
+
+options :: [OptDescr (Options -> Options)]
+options =
+ [ Option
+ ['p']
+ ["parse"]
+ (NoArg (\opts -> opts {optParse = True}))
+ "only parse, reporting any errors",
+ Option
+ ['h']
+ ["help"]
+ (NoArg (\opts -> opts {optHelp = True}))
+ "show help",
+ Option
+ ['v']
+ ["version"]
+ (NoArg (\opts -> opts {optVersion = True}))
+ "output version and exit"
+ ]
+
+usage :: String -> [String] -> IO ()
+usage progName errs
+ | null errs = do
+ putStrLn helpText
+ exitSuccess
+ | otherwise = do
+ hPutStrLn stderr ("error: " ++ concat errs ++ "Try " ++ progName ++ " -h for more information.")
+ exitFailure
+ where
+ header =
+ "Usage: "
+ ++ progName
+ ++ " [OPTION...] file"
+ helpText =
+ usageInfo header options
+
+compileFile :: String -> Bool -> IO ()
+compileFile filename onlyParse = do
+ res <- parseFromFile (scan parse) filename
+ case res of
+ Left err -> hPutStrLn stderr (showParserError err) >> exitFailure
+ Right ast -> do
+ res <- return $ evalState (compileAll ast) startState
+ case res of
+ Right _ -> if onlyParse then exitSuccess else print ast
+ Left errs -> hPutStr stderr (showErrorList errs) >> exitFailure
+
+main :: IO ()
+main = do
+ progName <- getProgName
+ argv <- getArgs
+ case getOpt Permute options argv of
+ (o, n, []) ->
+ do
+ when (optHelp opts) $ usage progName []
+ when (optVersion opts) $ putStrLn (progName ++ " " ++ version) >> exitSuccess
+ case n of
+ [filename] -> compileFile filename $ optParse opts
+ _ -> usage progName []
+ where
+ opts = foldl (flip id) defOptions o
+ (_, _, errs) -> usage progName errs