{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} module Hcompta.CLI.Command.GL where import Control.Applicative ((<$>)) import Control.Arrow (first) import Control.Monad (Monad(..), forM_, liftM, mapM) import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Except (runExceptT) import Data.Bool import Data.Either (Either(..), partitionEithers) import Data.Foldable (Foldable(..)) import Data.List ((++), repeat) import qualified Data.Map.Strict as Data.Map import Data.Maybe (Maybe(..), maybe) import Data.Monoid (Monoid(..), (<>)) import qualified Data.Sequence import qualified Data.Strict.Maybe as Strict import Data.String (String) import qualified Data.Text as Text import Data.Tuple (snd) import Prelude (($), (.), FilePath, IO, id, flip, unlines, zipWith) import Text.Show (Show(..)) import System.Console.GetOpt ( ArgDescr(..) , OptDescr(..) , usageInfo ) import System.Environment as Env (getProgName) import System.Exit (exitSuccess) import qualified System.IO as IO import Hcompta.Account (Account) import Hcompta.Amount (Amount) import qualified Hcompta.Amount as Amount import qualified Hcompta.Amount.Write as Amount.Write import Hcompta.Chart (Chart) import qualified Hcompta.Chart as Chart import qualified Hcompta.CLI.Args as Args import qualified Hcompta.CLI.Context as C import qualified Hcompta.CLI.Format.Ledger as CLI.Ledger import qualified Hcompta.CLI.Lang as Lang import qualified Hcompta.CLI.Lib.Leijen.Table as Table import qualified Hcompta.CLI.Write as Write import Hcompta.Date (Date) import qualified Hcompta.Date.Write as Date.Write import qualified Hcompta.Filter as Filter import qualified Hcompta.Filter.Read as Filter.Read 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 Hcompta.Lib.Leijen (toDoc, ToDoc(..)) import qualified Hcompta.Lib.Leijen as W import qualified Hcompta.Lib.TreeMap as TreeMap import Hcompta.GL (GL(..)) import qualified Hcompta.GL as GL import qualified Hcompta.Posting as Posting import qualified Hcompta.Tag as Tag data Ctx = Ctx { ctx_input :: [FilePath] , ctx_output :: [(Write.Mode, FilePath)] , ctx_filter_transaction :: Filter.Simplified (Filter.Filter_Bool (Filter.Filter_Transaction (Chart, Ledger.Transaction))) , ctx_filter_posting :: Filter.Simplified (Filter.Filter_Bool (Filter.Filter_Posting (Chart, Ledger.Posting))) , ctx_filter_gl :: Filter.Simplified (Filter.Filter_Bool (Filter.Filter_GL ( (Account, Tag.Tags) , Date , Amount.Sum Amount , Amount.Sum Amount ))) , ctx_reduce_date :: Bool } deriving (Show) nil :: Ctx nil = Ctx { ctx_filter_gl = mempty , ctx_filter_posting = mempty , ctx_filter_transaction = mempty , ctx_input = [] , ctx_output = [] , ctx_reduce_date = True } usage :: C.Context -> IO String usage c = do bin <- Env.getProgName return $ unlines $ [ C.translate c Lang.Section_Description , " "++C.translate c Lang.Help_Command_General_Ledger , "" , C.translate c Lang.Section_Syntax , " "++bin++" gl ["++C.translate c Lang.Type_Option++"] [...]"++ " ["++C.translate c Lang.Type_File_Journal++"] [...]" , "" , usageInfo (C.translate c Lang.Section_Options) (options c) ] options :: C.Context -> Args.Options Ctx options c = [ Option "g" ["filter-gl"] (ReqArg (\s ctx -> do ctx_filter_gl <- liftM ((ctx_filter_gl ctx <>) . Filter.simplify) $ liftIO $ Filter.Read.read Filter.Read.filter_gl s >>= \f -> case f of Left ko -> Write.fatal c $ ko Right ok -> return ok return $ ctx{ctx_filter_gl}) $ C.translate c Lang.Type_Filter_General_Ledger) $ C.translate c Lang.Help_Option_Filter_General_Ledger , Option "p" ["filter-posting"] (ReqArg (\s ctx -> do ctx_filter_posting <- liftM ((ctx_filter_posting ctx <>) . Filter.simplify) $ liftIO $ Filter.Read.read Filter.Read.filter_posting s >>= \f -> case f of Left ko -> Write.fatal c $ ko Right ok -> return ok return $ ctx{ctx_filter_posting}) $ C.translate c Lang.Type_Filter_Posting) $ C.translate c Lang.Help_Option_Filter_Posting , Option "t" ["filter-transaction"] (ReqArg (\s ctx -> do ctx_filter_transaction <- liftM ((ctx_filter_transaction ctx <>) . Filter.simplify) $ liftIO $ Filter.Read.read Filter.Read.filter_transaction s >>= \f -> case f of Left ko -> Write.fatal c $ ko Right ok -> return ok return $ ctx{ctx_filter_transaction}) $ C.translate c Lang.Type_Filter_Transaction) $ C.translate c Lang.Help_Option_Filter_Transaction , Option "h" ["help"] (NoArg (\_ctx -> do usage c >>= IO.hPutStr IO.stderr exitSuccess)) $ C.translate c Lang.Help_Option_Help , Option "i" ["input"] (ReqArg (\s ctx -> do return $ ctx{ctx_input=s:ctx_input ctx}) $ C.translate c Lang.Type_File_Journal) $ C.translate c Lang.Help_Option_Input , Option "o" ["output"] (ReqArg (\s ctx -> do return $ ctx{ctx_output=(Write.Mode_Append, s):ctx_output ctx}) $ C.translate c Lang.Type_File) $ C.translate c Lang.Help_Option_Output , Option "O" ["overwrite"] (ReqArg (\s ctx -> do return $ ctx{ctx_output=(Write.Mode_Over, s):ctx_output ctx}) $ C.translate c Lang.Type_File) $ C.translate c Lang.Help_Option_Overwrite {- NOTE: not used so far. , Option "" ["reduce-date"] (OptArg (\arg c ctx -> do ctx_reduce_date <- case arg of Nothing -> return $ True Just "yes" -> return $ True Just "no" -> return $ False Just _ -> Write.fatal c $ W.text "--reduce-date option expects \"yes\", or \"no\" as value" return $ ctx{ctx_reduce_date}) "[yes|no]") "use advanced date reducer to speed up filtering" -} ] run :: C.Context -> [String] -> IO () run c args = do (ctx, inputs) <- first (\x -> case ctx_output x of [] -> x{ctx_output=[(Write.Mode_Append, "-")]} _ -> x) <$> Args.parse c usage options (nil, args) read_journals <- liftM Data.Either.partitionEithers $ do CLI.Ledger.paths c $ ctx_input ctx ++ inputs >>= do mapM $ \path -> do liftIO $ runExceptT $ Ledger.Read.file (Ledger.Read.context ( ctx_filter_transaction ctx , ctx_filter_posting ctx ) Ledger.journal) path >>= \x -> case x of Left ko -> return $ Left (path, ko) Right ok -> return $ Right ok case read_journals of (errs@(_:_), _journals) -> forM_ errs $ \(_path, err) -> do Write.fatal c $ err ([], journals) -> do Write.debug c $ "filter: transaction: " ++ show (ctx_filter_transaction ctx) Write.debug c $ "filter: posting: " ++ show (ctx_filter_posting ctx) Write.debug c $ "filter: gl: " ++ show (ctx_filter_gl ctx) let gl = ledger_gl ctx journals let lang = C.lang c Write.write c Write.style (ctx_output ctx) $ do toDoc () $ do zipWith id [ Table.column (Lang.translate lang Lang.Title_Account) Table.Align_Left , Table.column (Lang.translate lang Lang.Title_Date) Table.Align_Left , Table.column (Lang.translate lang Lang.Title_Debit) Table.Align_Right , Table.column (Lang.translate lang Lang.Title_Credit) Table.Align_Right , Table.column (Lang.translate lang Lang.Title_Running_debit) Table.Align_Right , Table.column (Lang.translate lang Lang.Title_Running_credit) Table.Align_Right , Table.column (Lang.translate lang Lang.Title_Running_balance) Table.Align_Right , Table.column (Lang.translate lang Lang.Title_Description) Table.Align_Left ] $ do write_gl gl (repeat []) ledger_gl :: Ctx -> [ Ledger.Journal (GL.GL (Chart, Ledger.Transaction)) ] -> GL (Chart, Ledger.Transaction) ledger_gl ctx journals = let (chart, gl) = Data.Foldable.foldl' (flip (\j -> flip mappend $ (Ledger.journal_chart j,) $ Ledger.Journal.fold (\Ledger.Journal { Ledger.journal_sections=g } -> mappend g ) j mempty )) mempty journals in GL.GL $ TreeMap.map_Maybe_with_Path (\acct expanded_lines -> case Data.Map.mapMaybeWithKey (\date seq_lines -> case Data.Foldable.foldMap (\line@GL.GL_Line { GL.gl_line_transaction = _t , GL.gl_line_posting = p , GL.gl_line_sum = s } -> if Filter.test (ctx_filter_gl ctx) ( (acct, Chart.account_tags acct chart) , date , Amount.sum $ snd $ Data.Map.elemAt 0 $ Ledger.posting_amounts $ snd p , snd . Data.Map.elemAt 0 <$> s ) then Data.Sequence.singleton line else Data.Sequence.empty ) seq_lines of m | Data.Sequence.null m -> Nothing m -> Just m ) (GL.inclusive expanded_lines) of m | Data.Map.null m -> Strict.Nothing m -> Strict.Just m ) $ GL.expanded gl write_gl :: GL (Chart, Ledger.Transaction) -> [[Table.Cell]] -> [[Table.Cell]] write_gl (GL gl) = flip (TreeMap.foldr_with_Path (\acct -> flip $ Data.Map.foldrWithKey (\date -> flip (Data.Foldable.foldr (\GL.GL_Line { GL.gl_line_transaction = t , GL.gl_line_posting = p , GL.gl_line_sum = s } -> flip (Data.Map.foldrWithKey (\unit amt -> do let ptype = Posting.Posting_Type_Regular let descr = Ledger.transaction_description $ snd t zipWith (:) [ Table.cell { Table.cell_content = Ledger.Write.account ptype acct , Table.cell_width = Ledger.Write.account_length ptype acct } , Table.cell { Table.cell_content = Date.Write.date date , Table.cell_width = Date.Write.date_length date } , Table.cell { Table.cell_content = maybe W.empty Amount.Write.amount (Amount.sumable_positive amt) , Table.cell_width = maybe 0 Amount.Write.amount_length (Amount.sumable_positive amt) } , Table.cell { Table.cell_content = maybe W.empty Amount.Write.amount (Amount.sumable_negative amt) , Table.cell_width = maybe 0 Amount.Write.amount_length (Amount.sumable_negative amt) } , Table.cell { Table.cell_content = maybe W.empty Amount.Write.amount (maybe Nothing (Data.Map.lookup unit) $ Amount.sum_positive s) , Table.cell_width = maybe 0 Amount.Write.amount_length (maybe Nothing (Data.Map.lookup unit) $ Amount.sum_positive s) } , Table.cell { Table.cell_content = maybe W.empty Amount.Write.amount (maybe Nothing (Data.Map.lookup unit) $ Amount.sum_negative s) , Table.cell_width = maybe 0 Amount.Write.amount_length (maybe Nothing (Data.Map.lookup unit) $ Amount.sum_negative s) } , Table.cell { Table.cell_content = maybe W.empty Amount.Write.amount (Data.Map.lookup unit $ Amount.sum_balance s) , Table.cell_width = maybe 0 Amount.Write.amount_length (Data.Map.lookup unit $ Amount.sum_balance s) } , Table.cell { Table.cell_content = toDoc () descr , Table.cell_width = Text.length descr } ] )) (Ledger.posting_amounts $ snd p) )) ) )) gl