module Main where import System import System.Console.GetOpt -- Default script options defaultOptions :: Options defaultOptions = Options { runScript = runLexer , lexerPath = "lexer.lex" , txtFiles = [] } -- Main function : does argument parsing main = do args <- getArgs let (optHelpers, nonOpt, msg) = getOpt Permute options args let scriptOptions = compose optHelpers defaultOptions -- this next line is not perfect, but I'm not shure I can do better... runScript scriptOptions scriptOptions -- Main script : use a lexer on stdin runLexer :: Options -> IO () runLexer opt = do let files = txtFiles opt wds <- if not $ null $ txtFiles opt then do cs <- mapM readFile $ txtFiles opt return $ concatMap lines cs else getContents >>= return . lines return () mkLexer :: Options -> IO () mkLexer opt = undefined -- Options declaration options :: [OptDescr (Options -> Options)] options = [ Option ['V'] ["version"] (NoArg showVersion) "show version number" , Option [] ["mklexer"] (NoArg setMkLexer) "build a lexer from a lexicon" ] -- Option parsing machinery -- Options type -- the main function is in the options so we can switch it according to the option given (ex: the --version option) data Options = Options { runScript :: Options -> IO () , lexerPath :: String , txtFiles :: [String] } -- Options helpers showVersion :: Options -> Options showVersion o = o { runScript = \_ -> do putStrLn $ "gfdoc : GF documentation tool version " ++ "???"--_VERSION exitWith ExitSuccess } setMkLexer :: Options -> Options setMkLexer o = o { runScript = mkLexer } -- Utilities -- this compose a list of function together compose :: [a -> a] -> a -> a compose fs v = foldl (flip (.)) id fs $ v