]> Git — Sourcephile - comptalang.git/blob - cli/Hcompta/CLI/Command.hs
Modif : CLI.Command.{Print => Journal}.
[comptalang.git] / cli / Hcompta / CLI / Command.hs
1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE TupleSections #-}
4 module Hcompta.CLI.Command where
5
6 import Data.Maybe (fromMaybe)
7 import qualified Data.Text.Lazy as TL
8 import System.Console.GetOpt
9 ( ArgDescr(..)
10 , OptDescr(..)
11 , usageInfo )
12 import System.Environment (getProgName)
13 import System.Exit (exitWith, ExitCode(..))
14 import qualified System.IO as IO
15
16 import qualified Hcompta.CLI.Args as Args
17 import qualified Hcompta.CLI.Command.Balance as Command.Balance
18 import qualified Hcompta.CLI.Command.GL as Command.GL
19 import qualified Hcompta.CLI.Command.Journal as Command.Journal
20 import Hcompta.CLI.Context (Context)
21 import qualified Hcompta.CLI.Context as Context
22 import qualified Hcompta.CLI.Lang as Lang
23 import qualified Hcompta.CLI.Write as Write
24 import Hcompta.Lib.Leijen ((<>))
25 import qualified Hcompta.Lib.Leijen as W
26
27 usage :: IO String
28 usage = do
29 bin <- getProgName
30 return $ unlines $
31 [ "SYNTAX "
32 , " "++bin++" [option..] <command> [arguments]"
33 , ""
34 , usageInfo "OPTIONS" options
35 , "COMMANDS (use "++bin++" <command> --help for specific help)"
36 , " journal [-i FILE] [-t TRANSACTION_FILTER] [-p POSTING_FILTER]"
37 , " balance [-i FILE] [-t TRANSACTION_FILTER] [-p POSTING_FILTER] BALANCE_FILTER"
38 , " gl [-i FILE] [-t TRANSACTION_FILTER] [-p POSTING_FILTER] GL_FILTER"
39 ]
40
41 options :: Args.Options Context
42 options =
43 [ Option "h" ["help"]
44 (NoArg (\_opts _context -> do
45 usage >>= IO.hPutStr IO.stderr
46 exitWith ExitSuccess))
47 "show this help"
48 , Option "v" ["verbosity"]
49 (OptArg (\arg _context context ->
50 case arg of
51 Nothing ->
52 case Context.verbosity context of
53 v | v < maxBound ->
54 return $ context{Context.verbosity=succ v}
55 _ -> return $ context
56 Just "error" -> return $ context{Context.verbosity=Context.Verbosity_Error}
57 Just "warn" -> return $ context{Context.verbosity=Context.Verbosity_Warn}
58 Just "info" -> return $ context{Context.verbosity=Context.Verbosity_Info}
59 Just "debug" -> return $ context{Context.verbosity=Context.Verbosity_Debug}
60 Just _ -> Write.fatal context $
61 W.text "--verbosity option expects \"error\", \"warn\", \"info\", or \"debug\" as value")
62 "error|warn|info|debug"
63 )
64 "increment or set verbosity level, can be use multiple times"
65 , Option "" ["color"]
66 (OptArg (\arg _context context -> do
67 color <- case arg of
68 Nothing -> return $ Just True
69 Just "always" -> return $ Just True
70 Just "never" -> return $ Just False
71 Just "auto" -> return $ Nothing
72 Just _ -> Write.fatal context $
73 W.text "--color option expects \"always\", \"auto\", or \"never\" as value"
74 return $ context{Context.color})
75 "[always|auto|never]")
76 "colorize output"
77 , Option "" ["lang"]
78 (ReqArg (\lang _context context -> do
79 return $ context{Context.lang =
80 fromMaybe (Context.lang context) $
81 Lang.lang_of_strings [lang]
82 })
83 "[xx|xx-XX]")
84 "RFC1766 / ISO 639-1 language code (eg, fr, en-GB, etc.)"
85 ]
86
87 run :: Context -> String -> [String] -> IO ()
88 run context cmd args =
89 case cmd of
90 "balance" -> Command.Balance.run context args
91 "gl" -> Command.GL.run context args
92 "journal" -> Command.Journal.run context args
93 _ -> usage >>= Write.fatal context .
94 ((W.text "unknown command: " <> (W.text $ TL.pack cmd) <> W.line) <>) .
95 W.text . TL.pack