module Main where import qualified Paths_hydrogen_cli as Paths import Hydrogen.Prelude.System import Hydrogen.CliArgs import H.Common (LogLevel) import qualified H.Dump as Dump import qualified H.Init as Init import qualified H.Run as Run showVersion :: IO () showVersion = putStrLn ("hydrogen v" ++ show (fromDataVersion Paths.version)) unknownCommand :: String -> IO () unknownCommand = printf "Unknown command \"%s\". Use \"help\" for a list of available commands.\n" unknownTopic :: String -> IO () unknownTopic = printf "Unknown topic \"%s\". Use \"help\" for a list of available topics.\n" showHelp :: String -> IO () showHelp topic = do let topic' = if null topic then "help" else topic filename <- Paths.getDataFileName ("help" topic' <.> "txt") exists <- doesFileExist filename if | exists -> readFile filename >>= putStr | otherwise -> unknownTopic topic main :: IO () main = do (options, switches, args) <- getOpts [ 'h' ~: switch "help" , 'V' ~: switch "version" , 'v' ~: switch "verbose" , 'v' ~: optarg "verbose" ~= "^(v{1,3}|[0-4])$" ] let (command, topic, _) = safeHeadAndTail2 "help" "" args vs = case options ! "verbose" of [x] -> x _ -> "" verbosity | switches ? "verbose" = 1 | null vs = 0 | all (== 'v') vs = 1 + length vs | otherwise = read vs logger (lvl :: LogLevel) | fromEnum lvl <= verbosity = hPutStrLn stderr | otherwise = void . return run f = f logger (drop 1 args) if | switches ? "version" -> showVersion | switches ? "help" -> showHelp command | otherwise -> case command of "help" -> showHelp topic "escape" -> mapM_ (putStrLn . escapeFileName) (drop 1 args) "unescape" -> mapM_ (maybe (return ()) putStrLn . unescapeFileName) (drop 1 args) "dump" -> run Dump.main "init" -> run Init.main "run" -> run Run.main cmd -> unknownCommand cmd