{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} module Hcompta.CLI.Command.GL where import Control.Applicative (Const(..)) import Control.Monad (liftM) import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Except (runExceptT) import qualified Data.Either import qualified Data.Foldable import qualified Data.Map.Strict as Data.Map import Data.Monoid ((<>)) import qualified Data.Sequence import qualified Data.Strict.Maybe as Strict import qualified Data.Text as Text import qualified Data.Text.Lazy as TL import Prelude hiding (foldr) 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 Hcompta.Account (Account) import Hcompta.Amount (Amount) import qualified Hcompta.Amount as Amount import qualified Hcompta.Amount.Write as Amount.Write 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.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 Lib.TreeMap import Hcompta.GL (GL(..)) import qualified Hcompta.GL as GL data Ctx = Ctx { ctx_input :: [FilePath] , ctx_filter_transaction :: Filter.Simplified (Filter.Filter_Bool (Filter.Filter_Transaction Ledger.Transaction)) , ctx_filter_posting :: Filter.Simplified (Filter.Filter_Bool (Filter.Filter_Posting Ledger.Posting)) , ctx_filter_gl :: Filter.Simplified (Filter.Filter_Bool (Filter.Filter_GL ( Account , 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_reduce_date = True } usage :: IO String usage = do bin <- Env.getProgName return $ unlines $ [ "SYNTAX " , " "++bin++" gl" , " [-t TRANSACTION_FILTER]" , " [-p POSTING_FILTER]" , " [-g GL_FILTER]" , " JOURNAL_FILE [...]" , "" , usageInfo "OPTIONS" options ] options :: Args.Options Ctx options = [ Option "g" ["filter-gl"] (ReqArg (\s context ctx -> do ctx_filter_gl <- liftM (\t -> (<>) (ctx_filter_gl ctx) (Filter.simplify t (Nothing::Maybe ( Account , Date , Amount.Sum Amount , Amount.Sum Amount )))) $ liftIO $ Filter.Read.read Filter.Read.filter_gl s >>= \f -> case f of Left ko -> Write.fatal context $ ko Right ok -> return ok return $ ctx{ctx_filter_gl}) "FILTER") "filter at general ledger level, multiple uses are merged with a logical AND" , Option "p" ["filter-posting"] (ReqArg (\s context ctx -> do ctx_filter_posting <- liftM (\t -> (<>) (ctx_filter_posting ctx) (Filter.simplify t (Nothing::Maybe Ledger.Posting))) $ liftIO $ Filter.Read.read Filter.Read.filter_posting s >>= \f -> case f of Left ko -> Write.fatal context $ ko Right ok -> return ok return $ ctx{ctx_filter_posting}) "FILTER") "filter at posting level, multiple uses are merged with a logical AND" , Option "t" ["filter-transaction"] (ReqArg (\s context ctx -> do ctx_filter_transaction <- liftM (\t -> (<>) (ctx_filter_transaction ctx) (Filter.simplify t (Nothing::Maybe Ledger.Transaction))) $ liftIO $ Filter.Read.read Filter.Read.filter_transaction s >>= \f -> case f of Left ko -> Write.fatal context $ ko Right ok -> return ok return $ ctx{ctx_filter_transaction}) "FILTER") "filter at transaction level, multiple uses are merged with a logical AND" , 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}) "JOURNAL_FILE") "read data from given file, multiple uses merge the data as would a concatenation do" , Option "" ["reduce-date"] (OptArg (\arg context ctx -> do ctx_reduce_date <- case arg of Nothing -> return $ True Just "yes" -> return $ True Just "no" -> return $ False Just _ -> Write.fatal context $ 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 :: Context.Context -> [String] -> IO () run context args = do (ctx, inputs) <- Args.parse context usage options (nil, args) read_journals <- do CLI.Ledger.paths context $ ctx_input ctx ++ inputs >>= do mapM $ \path -> do liftIO $ runExceptT $ Ledger.Read.file (Ledger.Read.context $ Ledger.journal { Ledger.journal_transactions=Const ( mempty , ctx_filter_transaction ctx , ctx_filter_posting ctx ) }) path >>= \x -> case x of Left ko -> return $ Left (path, ko) Right ok -> return $ Right ok >>= return . Data.Either.partitionEithers case read_journals of (errs@(_:_), _journals) -> (flip mapM_) errs $ \(_path, err) -> do Write.fatal context $ err ([], journals) -> do Write.debug context $ "filter: transaction: " ++ show (ctx_filter_transaction ctx) Write.debug context $ "filter: posting: " ++ show (ctx_filter_posting ctx) Write.debug context $ "filter: gl: " ++ show (ctx_filter_gl ctx) let gl = ledger_gl ctx journals style_color <- Write.with_color context IO.stdout W.displayIO IO.stdout $ W.renderPretty style_color 1.0 maxBound $ do toDoc () $ let title = TL.toStrict . W.displayT . W.renderCompact False . toDoc (Context.lang context) in zipWith id [ Table.column (title Lang.Message_Account) Table.Align_Left , Table.column (title Lang.Message_Date) Table.Align_Left , Table.column (title Lang.Message_Debit) Table.Align_Right , Table.column (title Lang.Message_Credit) Table.Align_Right , Table.column (title Lang.Message_Running_debit) Table.Align_Right , Table.column (title Lang.Message_Running_credit) Table.Align_Right , Table.column (title Lang.Message_Running_balance) Table.Align_Right , Table.column (title Lang.Message_Description) Table.Align_Left ] $ write_gl gl (repeat []) ledger_gl :: Ctx -> [Ledger.Journal (Const ( GL.GL Ledger.Transaction , Filter.Simplified (Filter.Filter_Bool (Filter.Filter_Transaction Ledger.Transaction)) , Filter.Simplified (Filter.Filter_Bool (Filter.Filter_Posting Ledger.Posting)) )) Ledger.Transaction ] -> GL Ledger.Transaction ledger_gl ctx journals = let gl = Data.Foldable.foldl' (flip $ Ledger.Journal.fold (\Ledger.Journal{Ledger.journal_transactions=Const (g, _, _)} -> mappend g)) mempty journals in GL.GL $ Lib.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 , date , Amount.sum $ snd $ Data.Map.elemAt 0 $ Ledger.posting_amounts 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 Ledger.Transaction -> [[Table.Cell]] -> [[Table.Cell]] write_gl (GL gl) = flip (Lib.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 = Ledger.Posting_Type_Regular let descr = Ledger.transaction_description 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 p) )) ) )) gl