{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} module Hcompta.CLI.Command.Balance where import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Except (runExceptT) import qualified Data.Either import qualified Data.Foldable import qualified Data.List import qualified Data.Map.Strict as Data.Map import qualified Data.Text.Lazy as TL import System.Console.GetOpt ( ArgDescr(..) , OptDescr(..) , usageInfo ) import System.Environment as Env (getProgName) import System.Exit (exitWith, ExitCode(..)) import qualified System.IO as IO import Text.Show.Pretty (ppShow) -- TODO: may be not necessary import qualified Hcompta.Calc.Balance as Balance import qualified Hcompta.CLI.Args as Args import qualified Hcompta.CLI.Context as Context import qualified Hcompta.CLI.Format.Ledger as CLI.Ledger import qualified Hcompta.CLI.Lib.Shakespeare.Leijen as I18N import qualified Hcompta.CLI.Lib.Leijen.Table as Table import qualified Hcompta.CLI.Write as Write import qualified Hcompta.Format.Ledger as Ledger import qualified Hcompta.Format.Ledger.Journal as Ledger.Journal import qualified Hcompta.Format.Ledger.Read as Ledger.Read import qualified Hcompta.Format.Ledger.Write as Ledger.Write import qualified Hcompta.Lib.TreeMap as Lib.TreeMap import qualified Hcompta.Lib.Leijen as W import Hcompta.Lib.Leijen (toDoc, ToDoc(..)) import qualified Hcompta.Model.Amount as Amount import Hcompta.Model.Amount (Amount, Unit) data Ctx = Ctx { ctx_input :: [FilePath] , ctx_redundant :: Bool } deriving (Eq, Show) nil :: Ctx nil = Ctx { ctx_input = [] , ctx_redundant = False } usage :: IO String usage = do bin <- Env.getProgName return $ unlines $ [ "SYNTAX " , " "++bin++" balance [option..]" , "" , usageInfo "OPTIONS" options ] options :: Args.Options Ctx options = [ Option "h" ["help"] (NoArg (\_context _ctx -> do usage >>= IO.hPutStr IO.stderr exitWith ExitSuccess)) "show this help" , Option "i" ["input"] (ReqArg (\s _context ctx -> do return $ ctx{ctx_input=s:ctx_input ctx}) "FILE") "read data from given file, can be use multiple times" , Option "" ["redundant"] (OptArg (\arg context ctx -> do redundant <- case arg of Nothing -> return $ True Just "yes" -> return $ True Just "no" -> return $ False Just _ -> Write.fatal context $ W.text "--redundant option expects \"yes\", or \"no\" as value" return $ ctx{ctx_redundant=redundant}) "[yes|no]") "also print accounts with zero amount or the same amounts than its ascending account" ] run :: Context.Context -> [String] -> IO () run context args = do (ctx, _) <- Args.parse context usage options (nil, args) koks <- do CLI.Ledger.paths context $ ctx_input ctx >>= do mapM $ \path -> do liftIO $ runExceptT $ Ledger.Read.file path >>= \x -> case x of Left ko -> return $ Left (path, ko) Right ok -> return $ Right ok >>= return . Data.Either.partitionEithers case koks of (kos@(_:_), _oks) -> (flip mapM_) kos $ \(_path, ko) -> do Write.debug context $ ppShow $ ko Write.fatal context $ toDoc context ko ([], journals) -> do let balance = Data.List.foldr (Ledger.Journal.fold (flip (Data.Foldable.foldr (flip (Data.Foldable.foldr ( flip Balance.union . Ledger.transaction_postings_balance)))) . Ledger.journal_transactions)) Balance.balance journals let expanded = Balance.expanded $ Balance.balance_by_account balance style_color <- Write.with_color context IO.stdout Ledger.Write.put Ledger.Write.Style { Ledger.Write.style_align = True , Ledger.Write.style_color } IO.stdout $ do toDoc () $ let title = TL.toStrict . W.displayT . W.renderCompact False . I18N.renderMessage Context.App (Context.langs context) in zipWith id [ Table.column (title Write.I18N_Balance_debit) Table.Align_Right , Table.column (title Write.I18N_Balance_credit) Table.Align_Right , Table.column (title Write.I18N_Balance_total) Table.Align_Right , Table.column (title Write.I18N_Account) Table.Align_Left ] $ flip (write_by_accounts ctx) expanded $ zipWith (:) [ Table.Cell_Line '=' 0 , Table.Cell_Line '=' 0 , Table.Cell_Line '=' 0 , Table.Cell_Line ' ' 0 ] $ write_by_amounts (repeat []) $ Data.Map.map Balance.unit_sum_amount (Balance.balance_by_unit balance) write_by_accounts :: Ctx -> [[Table.Cell]] -> Balance.Expanded Amount Unit -> [[Table.Cell]] write_by_accounts ctx = let posting_type = Ledger.Posting_Type_Regular in Lib.TreeMap.foldr_with_Path_and_Node (\account node balance rows -> do let descendants = Lib.TreeMap.nodes (Lib.TreeMap.node_descendants node) let is_worth = ctx_redundant ctx || Data.Map.size (Data.Map.filter (not . Amount.is_zero) (Balance.exclusive balance)) > 0 || Data.Map.size (Data.Map.filter ( maybe False (not . Amount.are_zero . Balance.amount_sum_balance . Balance.inclusive) . Lib.TreeMap.node_value ) descendants) > 1 case is_worth of False -> rows True -> Data.List.foldr (\(amount_positive, amount_negative, amount) -> zipWith (:) [ Table.cell { Table.cell_content = maybe W.empty Ledger.Write.amount amount_positive , Table.cell_width = maybe 0 Ledger.Write.amount_length amount_positive } , Table.cell { Table.cell_content = maybe W.empty Ledger.Write.amount amount_negative , Table.cell_width = maybe 0 Ledger.Write.amount_length amount_negative } , Table.cell { Table.cell_content = Ledger.Write.amount $ amount , Table.cell_width = Ledger.Write.amount_length $ amount } , Table.cell { Table.cell_content = Ledger.Write.account posting_type account , Table.cell_width = Ledger.Write.account_length posting_type account } ] ) rows (zipWith3 (,,) ((map Just $ Data.Map.elems $ Balance.amount_sum_positive $ Balance.inclusive balance) ++ repeat Nothing) ((map Just $ Data.Map.elems $ Balance.amount_sum_negative $ Balance.inclusive balance) ++ repeat Nothing) (Data.Map.elems $ Balance.amount_sum_balance $ Balance.inclusive balance)) ) write_by_amounts :: [[Table.Cell]] -> Data.Map.Map Unit (Balance.Amount_Sum Amount ()) -> [[Table.Cell]] write_by_amounts = Data.Map.foldr (\amount_sum -> zipWith (:) [ let amt = Data.Map.lookup () $ Balance.amount_sum_positive amount_sum in Table.cell { Table.cell_content = maybe W.empty Ledger.Write.amount amt , Table.cell_width = maybe 0 Ledger.Write.amount_length amt } , let amt = Data.Map.lookup () $ Balance.amount_sum_negative amount_sum in Table.cell { Table.cell_content = maybe W.empty Ledger.Write.amount amt , Table.cell_width = maybe 0 Ledger.Write.amount_length amt } , let amt = Data.Map.lookup () $ Balance.amount_sum_balance amount_sum in Table.cell { Table.cell_content = maybe W.empty Ledger.Write.amount amt , Table.cell_width = maybe 0 Ledger.Write.amount_length amt } , Table.cell { Table.cell_content = W.empty , Table.cell_width = 0 } ] )