]> Git — Sourcephile - comptalang.git/blob - cli/Hcompta/CLI/Command.hs
Ajout : GL (General Ledger).
[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.Print as Command.Print
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 , " balance [-i FILE]"
37 , " print [-i FILE]"
38 ]
39
40 options :: Args.Options Context
41 options =
42 [ Option "h" ["help"]
43 (NoArg (\_opts _context -> do
44 usage >>= IO.hPutStr IO.stderr
45 exitWith ExitSuccess))
46 "show this help"
47 , Option "v" ["verbosity"]
48 (OptArg (\arg _context context ->
49 case arg of
50 Nothing ->
51 case Context.verbosity context of
52 v | v < maxBound ->
53 return $ context{Context.verbosity=succ v}
54 _ -> return $ context
55 Just "error" -> return $ context{Context.verbosity=Context.Verbosity_Error}
56 Just "warn" -> return $ context{Context.verbosity=Context.Verbosity_Warn}
57 Just "info" -> return $ context{Context.verbosity=Context.Verbosity_Info}
58 Just "debug" -> return $ context{Context.verbosity=Context.Verbosity_Debug}
59 Just _ -> Write.fatal context $
60 W.text "--verbosity option expects \"error\", \"warn\", \"info\", or \"debug\" as value")
61 "error|warn|info|debug"
62 )
63 "increment or set verbosity level, can be use multiple times"
64 , Option "" ["color"]
65 (OptArg (\arg _context context -> do
66 color <- case arg of
67 Nothing -> return $ Just True
68 Just "always" -> return $ Just True
69 Just "never" -> return $ Just False
70 Just "auto" -> return $ Nothing
71 Just _ -> Write.fatal context $
72 W.text "--color option expects \"always\", \"auto\", or \"never\" as value"
73 return $ context{Context.color})
74 "[always|auto|never]")
75 "colorize output"
76 , Option "" ["lang"]
77 (ReqArg (\lang _context context -> do
78 return $ context{Context.lang =
79 fromMaybe (Context.lang context) $
80 Lang.lang_of_strings [lang]
81 })
82 "[xx|xx-XX]")
83 "RFC1766 / ISO 639-1 language code (eg, fr, en-GB, etc.)"
84 ]
85
86 run :: Context -> String -> [String] -> IO ()
87 run context cmd args =
88 case cmd of
89 "print" -> Command.Print.run context args
90 "balance" -> Command.Balance.run context args
91 "gl" -> Command.GL.run context args
92 _ -> usage >>= Write.fatal context .
93 ((W.text "unknown command: " <> (W.text $ TL.pack cmd) <> W.line) <>) .
94 W.text . TL.pack