1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE TupleSections #-}
4 module Hcompta.CLI.Command.Balance where
6 import Control.Monad.IO.Class (liftIO)
7 import Control.Monad.Trans.Except (runExceptT)
8 import qualified Data.Either
9 import qualified Data.Foldable
10 import qualified Data.List
11 import qualified Data.Map
12 import qualified Data.Text.Lazy as TL
13 import System.Console.GetOpt
18 import System.Environment as Env (getProgName)
19 import System.Exit (exitWith, ExitCode(..))
20 import qualified System.IO as IO
21 import Text.Show.Pretty (ppShow)
23 import qualified Hcompta.CLI.Args as Args
24 import qualified Hcompta.CLI.Context as Context
25 import qualified Hcompta.CLI.Format.Ledger as CLI.Ledger
26 import qualified Hcompta.CLI.Write as Write
27 import qualified Hcompta.Calc.Balance as Balance
28 import qualified Hcompta.Format.Ledger.Journal
29 import qualified Hcompta.Format.Ledger.Read as Ledger.Read
30 import qualified Hcompta.Format.Ledger.Write as Ledger.Write
31 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
32 import qualified Hcompta.Lib.Leijen as W
33 import Hcompta.Lib.Leijen ((<>))
34 import qualified Hcompta.Model.Amount as Amount
35 import qualified Hcompta.Model.Transaction.Posting as Posting
36 -- import qualified Hcompta.Format.Ledger.Write
40 { ctx_input :: [FilePath]
41 , ctx_redundant :: Bool
48 , ctx_redundant = False
53 bin <- Env.getProgName
56 , " "++bin++" balance [option..]"
58 , usageInfo "OPTIONS" options
61 options :: Args.Options Ctx
64 (NoArg (\_context _ctx -> do
65 usage >>= IO.hPutStr IO.stderr
66 exitWith ExitSuccess))
68 , Option "i" ["input"]
69 (ReqArg (\s _context ctx -> do
70 return $ ctx{ctx_input=s:ctx_input ctx}) "FILE")
71 "read data from given file, can be use multiple times"
72 , Option "" ["redundant"]
73 (OptArg (\arg context ctx -> do
74 redundant <- case arg of
75 Nothing -> return $ True
76 Just "yes" -> return $ True
77 Just "no" -> return $ False
78 Just _ -> Write.fatal context
79 "--redundant option expects \"yes\", or \"no\" as value"
80 return $ ctx{ctx_redundant=redundant})
82 "also print accounts with zero amount or the same amounts than its ascending account"
85 run :: Context.Context -> [String] -> IO ()
87 (ctx, _) <- Args.parse context usage options (nil, args)
89 CLI.Ledger.paths context $ ctx_input ctx
90 >>= do mapM $ \path -> do
94 Left ko -> return $ Left (path, ko)
95 Right ok -> return $ Right ok
96 >>= return . Data.Either.partitionEithers
99 (flip mapM_) kos $ \(_path, ko) ->
100 Write.fatal context $ ko
102 CLI.Ledger.equilibre context journals
105 (\b j -> Balance.journal_with_virtual
106 (Hcompta.Format.Ledger.Journal.to_Model j) b)
109 Write.debug context $ ppShow $ balance
110 Write.debug context $ ppShow $
111 Lib.TreeMap.flatten (const ()) (Balance.by_account balance)
112 let expanded = Balance.expand $ Balance.by_account balance
113 Write.debug context $ ppShow $ expanded
114 with_color <- Write.with_color context IO.stdout
115 Ledger.Write.put with_color IO.stdout $ do
116 let (max_amount_length, accounts) = write_accounts ctx expanded
118 (W.bold $ W.dullblack $
119 W.text (TL.pack $ replicate max_amount_length '-') <>
120 (if max_amount_length <= 0 then W.empty else W.line)) <> do
121 write_amounts max_amount_length $
122 Data.Map.map Balance.amount $
123 (Balance.by_unit balance)
125 write_accounts :: Ctx -> Balance.Expanded -> (Int, W.Doc)
126 write_accounts ctx accounts = do
127 let max_amount_length =
130 (\(len, plus) Balance.Account_Sum_Expanded{Balance.inclusive=amounts} ->
131 let amounts_ = (if ctx_redundant ctx then amounts else Data.Map.filter (not . Amount.is_zero) amounts) in
132 ( Data.Map.foldr (max . Ledger.Write.amount_length) len amounts
133 , (if Data.Map.size amounts_ > 1
134 then 2 -- NOTE: length "+ "
139 (max_amount_length,) $ do
140 Lib.TreeMap.foldl_with_Path_and_Node
141 (\doc account node amounts ->
142 let descendants = Lib.TreeMap.nodes (Lib.TreeMap.node_descendants node) in
143 if not (ctx_redundant ctx) && (
144 Data.Map.null (Balance.exclusive amounts) ||
147 ( maybe False (not . Amount.are_zero . Balance.inclusive)
148 . Lib.TreeMap.node_content
153 doc <> Data.Map.foldl
155 if not (ctx_redundant ctx) && Amount.is_zero amount
161 W.fill (max_amount_length - Ledger.Write.amount_length amount) W.empty <> do
162 Ledger.Write.amount amount <> do
163 W.space <> W.space <> do
164 Ledger.Write.account Posting.Type_Regular account
166 (W.bold $ W.dullblack $ W.text "+" <> W.space) <> do
167 W.fill (max_amount_length - Ledger.Write.amount_length amount - 2) W.empty <> do
168 Ledger.Write.amount amount) <> do
170 ) W.empty (Balance.inclusive amounts)
174 write_amounts :: Int -> Amount.By_Unit -> W.Doc
175 write_amounts max_amount_length_ amounts = do
176 let max_amount_length =
178 (max . Ledger.Write.amount_length)
179 max_amount_length_ amounts
180 (if Data.Map.size amounts > 1
181 then W.space <> W.space
184 (W.line <> (W.bold $ W.dullblack $ W.text "+") <> W.space)
188 - Ledger.Write.amount_length amount
189 - (if Data.Map.size amounts > 1
190 then 2 -- NOTE: length "+ "
192 W.fill len W.empty <> do
193 Ledger.Write.amount amount)
195 (if Data.Map.null amounts then W.empty else W.line)