1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE TupleSections #-}
4 module Hcompta.CLI.Command where
6 import Data.Maybe (fromMaybe)
7 import qualified Data.Text.Lazy as TL
8 import System.Console.GetOpt
12 import System.Environment (getProgName)
13 import System.Exit (exitWith, ExitCode(..))
14 import qualified System.IO as IO
16 import Hcompta.CLI.Context (Context)
17 import qualified Hcompta.CLI.Args as Args
18 import qualified Hcompta.CLI.Command.Balance as Command.Balance
19 import qualified Hcompta.CLI.Command.Print as Command.Print
20 import qualified Hcompta.CLI.Context as Context
21 import qualified Hcompta.CLI.Lang as Lang
22 import qualified Hcompta.CLI.Write as Write
23 import qualified Hcompta.Lib.Leijen as W
24 import Hcompta.Lib.Leijen ((<>))
31 , " "++bin++" [option..] <command> [arguments]"
33 , usageInfo "OPTIONS" options
34 , "COMMANDS (use "++bin++" <command> --help for specific help)"
35 , " balance [-i FILE]"
39 options :: Args.Options Context
42 (NoArg (\_opts _context -> do
43 usage >>= IO.hPutStr IO.stderr
44 exitWith ExitSuccess))
46 , Option "v" ["verbosity"]
47 (OptArg (\arg _context context ->
50 case Context.verbosity context of
52 return $ context{Context.verbosity=succ v}
54 Just "error" -> return $ context{Context.verbosity=Context.Verbosity_Error}
55 Just "warn" -> return $ context{Context.verbosity=Context.Verbosity_Warn}
56 Just "info" -> return $ context{Context.verbosity=Context.Verbosity_Info}
57 Just "debug" -> return $ context{Context.verbosity=Context.Verbosity_Debug}
58 Just _ -> Write.fatal context $
59 W.text "--verbosity option expects \"error\", \"warn\", \"info\", or \"debug\" as value")
60 "error|warn|info|debug"
62 "increment or set verbosity level, can be use multiple times"
64 (OptArg (\arg _context context -> do
66 Nothing -> return $ Just True
67 Just "always" -> return $ Just True
68 Just "never" -> return $ Just False
69 Just "auto" -> return $ Nothing
70 Just _ -> Write.fatal context $
71 W.text "--color option expects \"always\", \"auto\", or \"never\" as value"
72 return $ context{Context.color})
73 "[always|auto|never]")
76 (ReqArg (\lang _context context -> do
77 return $ context{Context.lang =
78 fromMaybe (Context.lang context) $
79 Lang.lang_of_strings [lang]
82 "RFC1766 / ISO 639-1 language code (eg, fr, en-GB, etc.)"
85 run :: Context -> String -> [String] -> IO ()
86 run context cmd args =
88 "print" -> Command.Print.run context args
89 "balance" -> Command.Balance.run context args
90 _ -> usage >>= Write.fatal context .
91 ((W.text "unknown command: " <> (W.text $ TL.pack cmd) <> W.line) <>) .