{-|

A ledger-compatible @balance@ command, with additional support for
multi-column reports.

Here is a description/specification for the balance command.  See also
"Hledger.Reports" -> \"Balance reports\".


/Basic balance report/

With no report interval (@--monthly@ etc.), hledger's balance
command emulates ledger's, showing accounts indented according to
hierarchy, along with their total amount posted (including subaccounts).

Here's an example. With @examples/sample.journal@, which defines the following account tree:

@
 assets
   bank
     checking
     saving
   cash
 expenses
   food
   supplies
 income
   gifts
   salary
 liabilities
   debts
@

the basic @balance@ command gives this output:

@
 $ hledger -f sample.journal balance
                 $-1  assets
                  $1    bank:saving
                 $-2    cash
                  $2  expenses
                  $1    food
                  $1    supplies
                 $-2  income
                 $-1    gifts
                 $-1    salary
                  $1  liabilities:debts
--------------------
                   0
@

Subaccounts are displayed indented below their parent. Only the account leaf name (the final part) is shown.
(With @--flat@, account names are shown in full and unindented.)

Each account's \"balance\" is the sum of postings in that account and any subaccounts during the report period.
When the report period includes all transactions, this is equivalent to the account's current balance.

The overall total of the highest-level displayed accounts is shown below the line.
(The @--no-total/-N@ flag prevents this.)

/Eliding and omitting/

Accounts which have a zero balance, and no non-zero subaccount
balances, are normally omitted from the report.
(The @--empty/-E@ flag forces such accounts to be displayed.)
Eg, above @checking@ is omitted because it has a zero balance and no subaccounts.

Accounts which have a single subaccount also being displayed, with the same balance,
are normally elided into the subaccount's line.
(The @--no-elide@ flag prevents this.)
Eg, above @bank@ is elided to @bank:saving@ because it has only a
single displayed subaccount (@saving@) and their balance is the same
($1). Similarly, @liabilities@ is elided to @liabilities:debts@.

/Date limiting/

The default report period is that of the whole journal, including all
known transactions. The @--begin\/-b@, @--end\/-e@, @--period\/-p@
options or @date:@/@date2:@ patterns can be used to report only
on transactions before and/or after specified dates.

/Depth limiting/

The @--depth@ option can be used to limit the depth of the balance report.
Eg, to see just the top level accounts (still including their subaccount balances):

@
$ hledger -f sample.journal balance --depth 1
                 $-1  assets
                  $2  expenses
                 $-2  income
                  $1  liabilities
--------------------
                   0
@

/Account limiting/

With one or more account pattern arguments, the report is restricted
to accounts whose name matches one of the patterns, plus their parents
and subaccounts. Eg, adding the pattern @o@ to the first example gives:

@
 $ hledger -f sample.journal balance o
                  $1  expenses:food
                 $-2  income
                 $-1    gifts
                 $-1    salary
--------------------
                 $-1
@

* The @o@ pattern matched @food@ and @income@, so they are shown.

* @food@'s parent (@expenses@) is shown even though the pattern didn't
  match it, to clarify the hierarchy. The usual eliding rules cause it to be elided here.

* @income@'s subaccounts are also shown.

/Multi-column balance report/

hledger's balance command will show multiple columns when a reporting
interval is specified (eg with @--monthly@), one column for each sub-period.

There are three accumulation strategies for multi-column balance report, indicated by
the heading:

* A \"period balance\" (or \"flow\") report (with @--change@, the default) shows the
  change of account balance in each period, which is equivalent to the sum of postings
  in each period. Here, checking's balance increased by 10 in Feb:

  > Change of balance (flow):
  >
  >                  Jan   Feb   Mar
  > assets:checking   20    10    -5

* A \"cumulative balance\" report (with @--cumulative@) shows the accumulated ending balance
  across periods, starting from zero at the report's start date.
  Here, 30 is the sum of checking postings during Jan and Feb:

  > Ending balance (cumulative):
  >
  >                  Jan   Feb   Mar
  > assets:checking   20    30    25

* A \"historical balance\" report (with @--historical/-H@) also shows ending balances,
  but it includes the starting balance from any postings before the report start date.
  Here, 130 is the balance from all checking postings at the end of Feb, including
  pre-Jan postings which created a starting balance of 100:

  > Ending balance (historical):
  >
  >                  Jan   Feb   Mar
  > assets:checking  120   130   125

/Eliding and omitting, 2/

Here's a (imperfect?) specification for the eliding/omitting behaviour:

* Each account is normally displayed on its own line.

* An account less deep than the report's max depth, with just one
interesting subaccount, and the same balance as the subaccount, is
non-interesting, and prefixed to the subaccount's line, unless
@--no-elide@ is in effect.

* An account with a zero inclusive balance and less than two interesting
subaccounts is not displayed at all, unless @--empty@ is in effect.

* Multi-column balance reports show full account names with no eliding
  (like @--flat@). Accounts (and periods) are omitted as described below.

/Which accounts to show in balance reports/

By default:

* single-column: accounts with non-zero balance in report period.
                 (With @--flat@: accounts with non-zero balance and postings.)

* change:        accounts with postings and non-zero period balance in any period

* cumulative:    accounts with non-zero cumulative balance in any period

* historical:    accounts with non-zero historical balance in any period

With @-E/--empty@:

* single-column: accounts with postings in report period

* change:        accounts with postings in report period

* cumulative:    accounts with postings in report period

* historical:    accounts with non-zero starting balance +
                 accounts with postings in report period

/Which periods (columns) to show in balance reports/

An empty period/column is one where no report account has any postings.
A zero period/column is one where no report account has a non-zero period balance.

Currently,

by default:

* single-column: N/A

* change:        all periods within the overall report period,
                 except for leading and trailing empty periods

* cumulative:    all periods within the overall report period,
                 except for leading and trailing empty periods

* historical:    all periods within the overall report period,
                 except for leading and trailing empty periods

With @-E/--empty@:

* single-column: N/A

* change:        all periods within the overall report period

* cumulative:    all periods within the overall report period

* historical:    all periods within the overall report period

/What to show in empty cells/

An empty periodic balance report cell is one which has no corresponding postings.
An empty cumulative/historical balance report cell is one which has no corresponding
or prior postings, ie the account doesn't exist yet.
Currently, empty cells show 0.

-}

{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE NamedFieldPuns       #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE RecordWildCards      #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE TemplateHaskell      #-}

module Hledger.Cli.Commands.Balance (
  balancemode
 ,balance
 ,balanceReportAsText
 ,balanceReportAsCsv
 ,balanceReportItemAsText
 ,multiBalanceRowAsCsvText
 ,multiBalanceRowAsTableText
 ,multiBalanceReportAsText
 ,multiBalanceReportAsCsv
 ,multiBalanceReportAsHtml
 ,multiBalanceReportHtmlRows
 ,multiBalanceReportHtmlFootRow
 ,balanceReportAsTable
 ,balanceReportTableAsText
 ,tests_Balance
) where

import Data.Default (def)
import Data.List (transpose, foldl', transpose)
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Data.Time (fromGregorian)
import System.Console.CmdArgs.Explicit as C
import Lucid as L
import Safe (headMay, maximumMay)
import Text.Tabular.AsciiWide as Tab

import Hledger
import Hledger.Cli.CliOptions
import Hledger.Cli.Utils
import Hledger.Read.CsvReader (CSV, printCSV)


-- | Command line options for this command.
balancemode :: Mode RawOpts
balancemode = CommandDoc
-> [Flag RawOpts]
-> [(CommandDoc, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
  $(embedFileRelative "Hledger/Cli/Commands/Balance.txt")
  (
    [[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"sum"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"sum")
      CommandDoc
"show sum of posting amounts (default)"
    -- XXX --budget[=DESCPAT], --forecast[=PERIODEXP], could be more consistent
    ,CommandDoc
-> [CommandDoc]
-> Update RawOpts
-> CommandDoc
-> CommandDoc
-> Flag RawOpts
forall a.
CommandDoc
-> [CommandDoc] -> Update a -> CommandDoc -> CommandDoc -> Flag a
flagOpt CommandDoc
"" [CommandDoc
"budget"] (\CommandDoc
s RawOpts
opts -> RawOpts -> Either CommandDoc RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either CommandDoc RawOpts)
-> RawOpts -> Either CommandDoc RawOpts
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc -> RawOpts -> RawOpts
setopt CommandDoc
"budget" CommandDoc
s RawOpts
opts) CommandDoc
"DESCPAT"
      ([CommandDoc] -> CommandDoc
unlines
      [ CommandDoc
"show sum of posting amounts together with budget goals defined by periodic"
      , CommandDoc
"transactions. With a DESCPAT argument (must be separated by = not space),"
      , CommandDoc
"use only periodic transactions with matching description"
      , CommandDoc
"(case insensitive substring match)."
      ])
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"valuechange"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"valuechange")
      CommandDoc
"show total change of value of period-end historical balances (caused by deposits, withdrawals, market price fluctuations)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"gain"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"gain")
      CommandDoc
"show unrealised capital gain/loss (historical balance value minus cost basis)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"change"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"change")
      CommandDoc
"accumulate amounts from column start to column end (in multicolumn reports, default)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"cumulative"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"cumulative")
      CommandDoc
"accumulate amounts from report start (specified by e.g. -b/--begin) to column end"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"historical",CommandDoc
"H"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"historical")
      CommandDoc
"accumulate amounts from journal start to column end (includes postings before report start date)\n "
    ]
    [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. [a] -> [a] -> [a]
++ Bool -> [Flag RawOpts]
flattreeflags Bool
True [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. [a] -> [a] -> [a]
++
    [[CommandDoc]
-> Update RawOpts -> CommandDoc -> CommandDoc -> Flag RawOpts
forall a.
[CommandDoc] -> Update a -> CommandDoc -> CommandDoc -> Flag a
flagReq  [CommandDoc
"drop"] (\CommandDoc
s RawOpts
opts -> RawOpts -> Either CommandDoc RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either CommandDoc RawOpts)
-> RawOpts -> Either CommandDoc RawOpts
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc -> RawOpts -> RawOpts
setopt CommandDoc
"drop" CommandDoc
s RawOpts
opts) CommandDoc
"N" CommandDoc
"omit N leading account name parts (in flat mode)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"average",CommandDoc
"A"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"average") CommandDoc
"show a row average column (in multicolumn reports)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"row-total",CommandDoc
"T"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"row-total") CommandDoc
"show a row total column (in multicolumn reports)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"no-total",CommandDoc
"N"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"no-total") CommandDoc
"omit the final total row"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"no-elide"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"no-elide") CommandDoc
"don't squash boring parent accounts (in tree mode); don't show only 2 commodities per amount"
    ,[CommandDoc]
-> Update RawOpts -> CommandDoc -> CommandDoc -> Flag RawOpts
forall a.
[CommandDoc] -> Update a -> CommandDoc -> CommandDoc -> Flag a
flagReq  [CommandDoc
"format"] (\CommandDoc
s RawOpts
opts -> RawOpts -> Either CommandDoc RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either CommandDoc RawOpts)
-> RawOpts -> Either CommandDoc RawOpts
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc -> RawOpts -> RawOpts
setopt CommandDoc
"format" CommandDoc
s RawOpts
opts) CommandDoc
"FORMATSTR" CommandDoc
"use this custom line format (in simple reports)"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"sort-amount",CommandDoc
"S"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"sort-amount") CommandDoc
"sort by amount instead of account code/name (in flat mode). With multiple columns, sorts by the row total, or by row average if that is displayed."
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"percent", CommandDoc
"%"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"percent") CommandDoc
"express values in percentage of each column's total"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"invert"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"invert") CommandDoc
"display all amounts with reversed sign"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"transpose"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"transpose") CommandDoc
"transpose rows and columns"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"commodity-column"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"commodity-column")
      CommandDoc
"show commodity symbols in a separate column, amounts as bare numbers, one row per commodity"
    ,[CommandDoc] -> Flag RawOpts
outputFormatFlag [CommandDoc
"txt",CommandDoc
"html",CommandDoc
"csv",CommandDoc
"json"]
    ,Flag RawOpts
outputFileFlag
    ]
  )
  [(CommandDoc, [Flag RawOpts])
generalflagsgroup1]
  [Flag RawOpts]
hiddenflags
  ([], Arg RawOpts -> Maybe (Arg RawOpts)
forall a. a -> Maybe a
Just (Arg RawOpts -> Maybe (Arg RawOpts))
-> Arg RawOpts -> Maybe (Arg RawOpts)
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Arg RawOpts
argsFlag CommandDoc
"[QUERY]")

-- | The balance command, prints a balance report.
balance :: CliOpts -> Journal -> IO ()
balance :: CliOpts -> Journal -> IO ()
balance opts :: CliOpts
opts@CliOpts{reportspec_ :: CliOpts -> ReportSpec
reportspec_=ReportSpec
rspec} Journal
j = case BalanceCalculation
balancecalc_ of
    BalanceCalculation
CalcBudget -> do  -- single or multi period budget report
      let reportspan :: DateSpan
reportspan = Journal -> ReportSpec -> DateSpan
reportSpan Journal
j ReportSpec
rspec
          budgetreport :: BudgetReport
budgetreport = ReportSpec -> BalancingOpts -> DateSpan -> Journal -> BudgetReport
budgetReport ReportSpec
rspec (InputOpts -> BalancingOpts
balancingopts_ (InputOpts -> BalancingOpts) -> InputOpts -> BalancingOpts
forall a b. (a -> b) -> a -> b
$ CliOpts -> InputOpts
inputopts_ CliOpts
opts) DateSpan
reportspan Journal
j
          render :: BudgetReport -> Text
render = case CommandDoc
fmt of
            CommandDoc
"txt"  -> ReportOpts -> BudgetReport -> Text
budgetReportAsText ReportOpts
ropts
            CommandDoc
"json" -> (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
"\n") (Text -> Text) -> (BudgetReport -> Text) -> BudgetReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BudgetReport -> Text
forall a. ToJSON a => a -> Text
toJsonText
            CommandDoc
"csv"  -> CSV -> Text
printCSV (CSV -> Text) -> (BudgetReport -> CSV) -> BudgetReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> BudgetReport -> CSV
budgetReportAsCsv ReportOpts
ropts
            CommandDoc
_      -> CommandDoc -> BudgetReport -> Text
forall a. CommandDoc -> a
error' (CommandDoc -> BudgetReport -> Text)
-> CommandDoc -> BudgetReport -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
unsupportedOutputFormatError CommandDoc
fmt
      CliOpts -> Text -> IO ()
writeOutputLazyText CliOpts
opts (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ BudgetReport -> Text
render BudgetReport
budgetreport

    BalanceCalculation
_ | Bool
multiperiod -> do  -- multi period balance report
        let report :: MultiBalanceReport
report = ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport ReportSpec
rspec Journal
j
            render :: MultiBalanceReport -> Text
render = case CommandDoc
fmt of
              CommandDoc
"txt"  -> ReportOpts -> MultiBalanceReport -> Text
multiBalanceReportAsText ReportOpts
ropts
              CommandDoc
"csv"  -> CSV -> Text
printCSV (CSV -> Text)
-> (MultiBalanceReport -> CSV) -> MultiBalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> MultiBalanceReport -> CSV
multiBalanceReportAsCsv ReportOpts
ropts
              CommandDoc
"html" -> (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
"\n") (Text -> Text)
-> (MultiBalanceReport -> Text) -> MultiBalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Html () -> Text
forall a. Html a -> Text
L.renderText (Html () -> Text)
-> (MultiBalanceReport -> Html ()) -> MultiBalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> MultiBalanceReport -> Html ()
multiBalanceReportAsHtml ReportOpts
ropts
              CommandDoc
"json" -> (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
"\n") (Text -> Text)
-> (MultiBalanceReport -> Text) -> MultiBalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MultiBalanceReport -> Text
forall a. ToJSON a => a -> Text
toJsonText
              CommandDoc
_      -> Text -> MultiBalanceReport -> Text
forall a b. a -> b -> a
const (Text -> MultiBalanceReport -> Text)
-> Text -> MultiBalanceReport -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Text
forall a. CommandDoc -> a
error' (CommandDoc -> Text) -> CommandDoc -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
unsupportedOutputFormatError CommandDoc
fmt  -- PARTIAL:
        CliOpts -> Text -> IO ()
writeOutputLazyText CliOpts
opts (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ MultiBalanceReport -> Text
render MultiBalanceReport
report

    BalanceCalculation
_ -> do  -- single period simple balance report
        let report :: BalanceReport
report = ReportSpec -> Journal -> BalanceReport
balanceReport ReportSpec
rspec Journal
j -- simple Ledger-style balance report
            render :: ReportOpts -> BalanceReport -> Text
render = case CommandDoc
fmt of
              CommandDoc
"txt"  -> \ReportOpts
ropts -> Builder -> Text
TB.toLazyText (Builder -> Text)
-> (BalanceReport -> Builder) -> BalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> BalanceReport -> Builder
balanceReportAsText ReportOpts
ropts
              CommandDoc
"csv"  -> \ReportOpts
ropts -> CSV -> Text
printCSV (CSV -> Text) -> (BalanceReport -> CSV) -> BalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> BalanceReport -> CSV
balanceReportAsCsv ReportOpts
ropts
              -- "html" -> \ropts -> (<>"\n") . L.renderText . multiBalanceReportAsHtml ropts . balanceReportAsMultiBalanceReport ropts
              CommandDoc
"json" -> (BalanceReport -> Text) -> ReportOpts -> BalanceReport -> Text
forall a b. a -> b -> a
const ((BalanceReport -> Text) -> ReportOpts -> BalanceReport -> Text)
-> (BalanceReport -> Text) -> ReportOpts -> BalanceReport -> Text
forall a b. (a -> b) -> a -> b
$ (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
"\n") (Text -> Text) -> (BalanceReport -> Text) -> BalanceReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BalanceReport -> Text
forall a. ToJSON a => a -> Text
toJsonText
              CommandDoc
_      -> CommandDoc -> ReportOpts -> BalanceReport -> Text
forall a. CommandDoc -> a
error' (CommandDoc -> ReportOpts -> BalanceReport -> Text)
-> CommandDoc -> ReportOpts -> BalanceReport -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
unsupportedOutputFormatError CommandDoc
fmt  -- PARTIAL:
        CliOpts -> Text -> IO ()
writeOutputLazyText CliOpts
opts (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ ReportOpts -> BalanceReport -> Text
render ReportOpts
ropts BalanceReport
report
  where
    ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Costing
StringFormat
Period
Interval
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
cost_ :: ReportOpts -> Costing
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe Text
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
commodity_column_ :: ReportOpts -> Bool
commodity_column_ :: Bool
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
balancecalc_ :: BalanceCalculation
..} = ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec
    multiperiod :: Bool
multiperiod = Interval
interval_ Interval -> Interval -> Bool
forall a. Eq a => a -> a -> Bool
/= Interval
NoInterval
    fmt :: CommandDoc
fmt         = CliOpts -> CommandDoc
outputFormatFromOpts CliOpts
opts

-- XXX this allows rough HTML rendering of a flat BalanceReport, but it can't handle tree mode etc.
-- -- | Convert a BalanceReport to a MultiBalanceReport.
-- balanceReportAsMultiBalanceReport :: ReportOpts -> BalanceReport -> MultiBalanceReport 
-- balanceReportAsMultiBalanceReport _ropts (britems, brtotal) = 
--   let
--     mbrrows = 
--       [PeriodicReportRow{
--           prrName    = flatDisplayName brfullname
--         , prrAmounts = [bramt]
--         , prrTotal   = bramt
--         , prrAverage = bramt
--         }
--       | (brfullname, _, _, bramt) <- britems
--       ]
--   in
--     PeriodicReport{
--         prDates  = [nulldatespan]
--       , prRows   = mbrrows
--       , prTotals = PeriodicReportRow{
--            prrName=()
--           ,prrAmounts=[brtotal]
--           ,prrTotal=brtotal
--           ,prrAverage=brtotal
--           }
--       }

-- XXX should all the per-report, per-format rendering code live in the command module,
-- like the below, or in the report module, like budgetReportAsText/budgetReportAsCsv ?

-- rendering single-column balance reports

-- | Render a single-column balance report as CSV.
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
balanceReportAsCsv ReportOpts
opts ([BalanceReportItem]
items, MixedAmount
total) =
  (Text
"account" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: ((if ReportOpts -> Bool
commodity_column_ ReportOpts
opts then (:) Text
"commodity" else [Text] -> [Text]
forall a. a -> a
id) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text
"balance"]))
  [Text] -> CSV -> CSV
forall a. a -> [a] -> [a]
:  ((BalanceReportItem -> CSV) -> [BalanceReportItem] -> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(Text
a, Text
_, Int
_, MixedAmount
b) -> Text -> MixedAmount -> CSV
rows Text
a MixedAmount
b) [BalanceReportItem]
items)
  CSV -> CSV -> CSV
forall a. [a] -> [a] -> [a]
++ if ReportOpts -> Bool
no_total_ ReportOpts
opts then [] else Text -> MixedAmount -> CSV
rows Text
"total" MixedAmount
total
  where
    rows :: AccountName -> MixedAmount -> [[T.Text]]
    rows :: Text -> MixedAmount -> CSV
rows Text
name MixedAmount
ma
      | ReportOpts -> Bool
commodity_column_ ReportOpts
opts =
          ((Text, Amount) -> [Text]) -> [(Text, Amount)] -> CSV
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Text
k, Amount
a) -> [Text -> Text
showName Text
name, Text
k, MixedAmount -> Text
renderAmount (MixedAmount -> Text) -> (Amount -> MixedAmount) -> Amount -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> MixedAmount
mixedAmount (Amount -> MixedAmount)
-> (Amount -> Amount) -> Amount -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Amount
amountStripPrices (Amount -> Text) -> Amount -> Text
forall a b. (a -> b) -> a -> b
$ Amount
a])
          ([(Text, Amount)] -> CSV)
-> (MixedAmount -> [(Text, Amount)]) -> MixedAmount -> CSV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Text Amount -> [(Text, Amount)]
forall k a. Map k a -> [(k, a)]
M.toList (Map Text Amount -> [(Text, Amount)])
-> (MixedAmount -> Map Text Amount)
-> MixedAmount
-> [(Text, Amount)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map Text Amount -> Amount -> Map Text Amount)
-> Map Text Amount -> [Amount] -> Map Text Amount
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Map Text Amount -> Amount -> Map Text Amount
sumAmounts Map Text Amount
forall a. Monoid a => a
mempty ([Amount] -> Map Text Amount)
-> (MixedAmount -> [Amount]) -> MixedAmount -> Map Text Amount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> [Amount]
amounts (MixedAmount -> CSV) -> MixedAmount -> CSV
forall a b. (a -> b) -> a -> b
$ MixedAmount
ma
      | Bool
otherwise = [[Text -> Text
showName Text
name, MixedAmount -> Text
renderAmount MixedAmount
ma]]

    showName :: Text -> Text
showName = Int -> Text -> Text
accountNameDrop (ReportOpts -> Int
drop_ ReportOpts
opts)
    renderAmount :: MixedAmount -> Text
renderAmount MixedAmount
amt = WideBuilder -> Text
wbToText (WideBuilder -> Text) -> WideBuilder -> Text
forall a b. (a -> b) -> a -> b
$ AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
bopts MixedAmount
amt
      where bopts :: AmountDisplayOpts
bopts = (Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts Bool
False ReportOpts
opts){displayOrder :: Maybe [Text]
displayOrder = Maybe [Text]
order}
            order :: Maybe [Text]
order = if ReportOpts -> Bool
commodity_column_ ReportOpts
opts then [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just (Set Text -> [Text]
forall a. Set a -> [a]
S.toList (Set Text -> [Text]) -> Set Text -> [Text]
forall a b. (a -> b) -> a -> b
$ MixedAmount -> Set Text
maCommodities MixedAmount
amt) else Maybe [Text]
forall a. Maybe a
Nothing
    sumAmounts :: Map Text Amount -> Amount -> Map Text Amount
sumAmounts Map Text Amount
mp Amount
am = (Amount -> Amount -> Amount)
-> Text -> Amount -> Map Text Amount -> Map Text Amount
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
M.insertWith Amount -> Amount -> Amount
forall a. Num a => a -> a -> a
(+) (Amount -> Text
acommodity Amount
am) Amount
am Map Text Amount
mp

-- | Render a single-column balance report as plain text.
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
balanceReportAsText :: ReportOpts -> BalanceReport -> Builder
balanceReportAsText ReportOpts
opts (([BalanceReportItem]
items, MixedAmount
total))
  | Bool -> Bool
not (ReportOpts -> Bool
commodity_column_ ReportOpts
opts) =
      [Builder] -> Builder
unlinesB [Builder]
lines
      Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [Builder] -> Builder
unlinesB (if ReportOpts -> Bool
no_total_ ReportOpts
opts then [] else [Builder
overline, Builder
totalLines])
  | Bool
iscustom = CommandDoc -> Builder
forall a. CommandDoc -> a
error' CommandDoc
"Custom format not supported with --commodity-column"   -- PARTIAL:
  | Bool
otherwise = ReportOpts -> BalanceReport -> Builder
balanceReportAsText' ReportOpts
opts (([BalanceReportItem]
items, MixedAmount
total))
  where
    ([Builder]
lines, [[Int]]
sizes) = [(Builder, [Int])] -> ([Builder], [[Int]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Builder, [Int])] -> ([Builder], [[Int]]))
-> [(Builder, [Int])] -> ([Builder], [[Int]])
forall a b. (a -> b) -> a -> b
$ (BalanceReportItem -> (Builder, [Int]))
-> [BalanceReportItem] -> [(Builder, [Int])]
forall a b. (a -> b) -> [a] -> [b]
map (ReportOpts -> BalanceReportItem -> (Builder, [Int])
balanceReportItemAsText ReportOpts
opts) [BalanceReportItem]
items
    -- abuse renderBalanceReportItem to render the total with similar format
    (Builder
totalLines, [Int]
_) = ReportOpts -> (Text, Int, MixedAmount) -> (Builder, [Int])
renderBalanceReportItem ReportOpts
opts (Text
"",Int
0,MixedAmount
total)
    -- with a custom format, extend the line to the full report width;
    -- otherwise show the usual 20-char line for compatibility
    iscustom :: Bool
iscustom = case ReportOpts -> StringFormat
format_ ReportOpts
opts of
        OneLine       ((FormatField Bool
_ Maybe Int
_ Maybe Int
_ ReportItemField
TotalField):[StringFormatComponent]
_) -> Bool
False
        TopAligned    ((FormatField Bool
_ Maybe Int
_ Maybe Int
_ ReportItemField
TotalField):[StringFormatComponent]
_) -> Bool
False
        BottomAligned ((FormatField Bool
_ Maybe Int
_ Maybe Int
_ ReportItemField
TotalField):[StringFormatComponent]
_) -> Bool
False
        StringFormat
_ -> Bool
True
    overlinewidth :: Int
overlinewidth = if Bool
iscustom then [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (([Int] -> Int) -> [[Int]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Int
forall a. Integral a => [a] -> a
maximum' ([[Int]] -> [Int]) -> [[Int]] -> [Int]
forall a b. (a -> b) -> a -> b
$ [[Int]] -> [[Int]]
forall a. [[a]] -> [[a]]
transpose [[Int]]
sizes) else Int
20
    overline :: Builder
overline   = Text -> Builder
TB.fromText (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.replicate Int
overlinewidth Text
"-"

-- | Render a single-column balance report as plain text in commodity-column mode
balanceReportAsText' :: ReportOpts -> BalanceReport -> TB.Builder
balanceReportAsText' :: ReportOpts -> BalanceReport -> Builder
balanceReportAsText' ReportOpts
opts (([BalanceReportItem]
items, MixedAmount
total)) =
  [Builder] -> Builder
unlinesB ([Builder] -> Builder)
-> ([[Cell]] -> [Builder]) -> [[Cell]] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Cell] -> Builder) -> [[Cell]] -> [Builder]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TableOpts -> [Int] -> Header Cell -> Builder
renderColumns TableOpts
forall a. Default a => a
def{tableBorders :: Bool
tableBorders=Bool
False} [Int]
sizes (Header Cell -> Builder)
-> ([Cell] -> Header Cell) -> [Cell] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  Properties -> [Header Cell] -> Header Cell
forall h. Properties -> [Header h] -> Header h
Tab.Group Properties
NoLine ([Header Cell] -> Header Cell)
-> ([Cell] -> [Header Cell]) -> [Cell] -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Cell -> Header Cell) -> [Cell] -> [Header Cell]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Cell -> Header Cell
forall h. h -> Header h
Header) ([[Cell]] -> Builder) -> [[Cell]] -> Builder
forall a b. (a -> b) -> a -> b
$
    [[Cell]]
lines [[Cell]] -> [[Cell]] -> [[Cell]]
forall a. [a] -> [a] -> [a]
++ [[[Cell]]] -> [[Cell]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[[Cell
overline], [Cell]
totalline] | Bool -> Bool
not (ReportOpts -> Bool
no_total_ ReportOpts
opts)]
  where
    render :: (a, Text, Int, MixedAmount) -> [Cell]
render (a
_, Text
acctname, Int
depth, MixedAmount
amt) =
        [ Align -> [WideBuilder] -> Cell
Cell Align
TopRight [WideBuilder]
damts
        , Align -> [WideBuilder] -> Cell
Cell Align
TopLeft ((Text -> WideBuilder) -> [Text] -> [WideBuilder]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> WideBuilder
wbFromText [Text]
cs)
        , Align -> [WideBuilder] -> Cell
Cell Align
TopLeft (Int -> WideBuilder -> [WideBuilder]
forall a. Int -> a -> [a]
replicate ([WideBuilder] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [WideBuilder]
damts Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) WideBuilder
forall a. Monoid a => a
mempty [WideBuilder] -> [WideBuilder] -> [WideBuilder]
forall a. [a] -> [a] -> [a]
++ [Text -> WideBuilder
wbFromText Text
dispname]) ]
      where dopts :: AmountDisplayOpts
dopts = (Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts Bool
True ReportOpts
opts){displayOrder :: Maybe [Text]
displayOrder=[Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
cs}
            cs :: [Text]
cs    = Set Text -> [Text]
forall a. Set a -> [a]
S.toList (Set Text -> [Text]) -> Set Text -> [Text]
forall a b. (a -> b) -> a -> b
$ MixedAmount -> Set Text
maCommodities MixedAmount
amt
            dispname :: Text
dispname = Int -> Text -> Text
T.replicate ((Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
acctname
            damts :: [WideBuilder]
damts = AmountDisplayOpts -> MixedAmount -> [WideBuilder]
showMixedAmountLinesB AmountDisplayOpts
dopts MixedAmount
amt
    lines :: [[Cell]]
lines = (BalanceReportItem -> [Cell]) -> [BalanceReportItem] -> [[Cell]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BalanceReportItem -> [Cell]
forall a. (a, Text, Int, MixedAmount) -> [Cell]
render [BalanceReportItem]
items
    totalline :: [Cell]
totalline = (CommandDoc, Text, Int, MixedAmount) -> [Cell]
forall a. (a, Text, Int, MixedAmount) -> [Cell]
render (CommandDoc
"", Text
"", Int
0, MixedAmount
total)
    sizes :: [Int]
sizes = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (Maybe Int -> Int) -> ([Cell] -> Maybe Int) -> [Cell] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Maybe Int
forall a. Ord a => [a] -> Maybe a
maximumMay ([Int] -> Maybe Int) -> ([Cell] -> [Int]) -> [Cell] -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Cell -> Int) -> [Cell] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Cell -> Int
cellWidth ([Cell] -> Int) -> [[Cell]] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
        [[Cell]] -> [[Cell]]
forall a. [[a]] -> [[a]]
transpose ([[Cell]
totalline | Bool -> Bool
not (ReportOpts -> Bool
no_total_ ReportOpts
opts)] [[Cell]] -> [[Cell]] -> [[Cell]]
forall a. [a] -> [a] -> [a]
++ [[Cell]]
lines)
    overline :: Cell
overline = Align -> [WideBuilder] -> Cell
Cell Align
TopLeft ([WideBuilder] -> Cell)
-> (Maybe Int -> [WideBuilder]) -> Maybe Int -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WideBuilder -> [WideBuilder]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WideBuilder -> [WideBuilder])
-> (Maybe Int -> WideBuilder) -> Maybe Int -> [WideBuilder]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> WideBuilder
wbFromText (Text -> WideBuilder)
-> (Maybe Int -> Text) -> Maybe Int -> WideBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Text -> Text) -> Text -> Int -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Text -> Text
T.replicate Text
"-" (Int -> Text) -> (Maybe Int -> Int) -> Maybe Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (Maybe Int -> Cell) -> Maybe Int -> Cell
forall a b. (a -> b) -> a -> b
$ [Int] -> Maybe Int
forall a. [a] -> Maybe a
headMay [Int]
sizes

{-
:r
This implementation turned out to be a bit convoluted but implements the following algorithm for formatting:

- If there is a single amount, print it with the account name directly:
- Otherwise, only print the account name on the last line.

    a         USD 1   ; Account 'a' has a single amount
              EUR -1
    b         USD -1  ; Account 'b' has two amounts. The account name is printed on the last line.
-}
-- | Render one balance report line item as plain text suitable for console output (or
-- whatever string format is specified). Note, prices will not be rendered, and
-- differently-priced quantities of the same commodity will appear merged.
-- The output will be one or more lines depending on the format and number of commodities.
balanceReportItemAsText :: ReportOpts -> BalanceReportItem -> (TB.Builder, [Int])
balanceReportItemAsText :: ReportOpts -> BalanceReportItem -> (Builder, [Int])
balanceReportItemAsText ReportOpts
opts (Text
_, Text
accountName, Int
depth, MixedAmount
amt) =
  ReportOpts -> (Text, Int, MixedAmount) -> (Builder, [Int])
renderBalanceReportItem ReportOpts
opts (Text
accountName, Int
depth, MixedAmount
amt)

-- | Render a balance report item using the given StringFormat, generating one or more lines of text.
renderBalanceReportItem :: ReportOpts -> (AccountName, Int, MixedAmount) -> (TB.Builder, [Int])
renderBalanceReportItem :: ReportOpts -> (Text, Int, MixedAmount) -> (Builder, [Int])
renderBalanceReportItem ReportOpts
opts (Text
acctname, Int
depth, MixedAmount
total) =
  case ReportOpts -> StringFormat
format_ ReportOpts
opts of
      OneLine       [StringFormatComponent]
comps -> [Cell] -> (Builder, [Int])
renderRow' ([Cell] -> (Builder, [Int])) -> [Cell] -> (Builder, [Int])
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> [StringFormatComponent] -> [Cell]
render Bool
True  Bool
True  [StringFormatComponent]
comps
      TopAligned    [StringFormatComponent]
comps -> [Cell] -> (Builder, [Int])
renderRow' ([Cell] -> (Builder, [Int])) -> [Cell] -> (Builder, [Int])
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> [StringFormatComponent] -> [Cell]
render Bool
True  Bool
False [StringFormatComponent]
comps
      BottomAligned [StringFormatComponent]
comps -> [Cell] -> (Builder, [Int])
renderRow' ([Cell] -> (Builder, [Int])) -> [Cell] -> (Builder, [Int])
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> [StringFormatComponent] -> [Cell]
render Bool
False Bool
False [StringFormatComponent]
comps
  where
    renderRow' :: [Cell] -> (Builder, [Int])
renderRow' [Cell]
is = ( TableOpts -> Header Cell -> Builder
renderRowB TableOpts
forall a. Default a => a
def{tableBorders :: Bool
tableBorders=Bool
False, borderSpaces :: Bool
borderSpaces=Bool
False}
                      (Header Cell -> Builder)
-> ([Header Cell] -> Header Cell) -> [Header Cell] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Properties -> [Header Cell] -> Header Cell
forall h. Properties -> [Header h] -> Header h
Tab.Group Properties
NoLine ([Header Cell] -> Builder) -> [Header Cell] -> Builder
forall a b. (a -> b) -> a -> b
$ (Cell -> Header Cell) -> [Cell] -> [Header Cell]
forall a b. (a -> b) -> [a] -> [b]
map Cell -> Header Cell
forall h. h -> Header h
Header [Cell]
is
                    , (Cell -> Int) -> [Cell] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Cell -> Int
cellWidth [Cell]
is )

    render :: Bool -> Bool -> [StringFormatComponent] -> [Cell]
render Bool
topaligned Bool
oneline = (StringFormatComponent -> Cell)
-> [StringFormatComponent] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map (Bool
-> Bool
-> ReportOpts
-> (Text, Int, MixedAmount)
-> StringFormatComponent
-> Cell
renderComponent Bool
topaligned Bool
oneline ReportOpts
opts (Text
acctname, Int
depth, MixedAmount
total))

-- | Render one StringFormat component for a balance report item.
renderComponent :: Bool -> Bool -> ReportOpts -> (AccountName, Int, MixedAmount) -> StringFormatComponent -> Cell
renderComponent :: Bool
-> Bool
-> ReportOpts
-> (Text, Int, MixedAmount)
-> StringFormatComponent
-> Cell
renderComponent Bool
_ Bool
_ ReportOpts
_ (Text, Int, MixedAmount)
_ (FormatLiteral Text
s) = Align -> Text -> Cell
textCell Align
TopLeft Text
s
renderComponent Bool
topaligned Bool
oneline ReportOpts
opts (Text
acctname, Int
depth, MixedAmount
total) (FormatField Bool
ljust Maybe Int
mmin Maybe Int
mmax ReportItemField
field) = case ReportItemField
field of
    ReportItemField
DepthSpacerField -> Align -> [WideBuilder] -> Cell
Cell Align
align [Builder -> Int -> WideBuilder
WideBuilder (Text -> Builder
TB.fromText (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.replicate Int
d Text
" ") Int
d]
                        where d :: Int
d = (Int -> Int) -> (Int -> Int -> Int) -> Maybe Int -> Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int -> Int
forall a. a -> a
id Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Maybe Int
mmax (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 Maybe Int
mmin
    ReportItemField
AccountField     -> Align -> Text -> Cell
textCell Align
align (Text -> Cell) -> Text -> Cell
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Int -> Maybe Int -> Text -> Text
formatText Bool
ljust Maybe Int
mmin Maybe Int
mmax Text
acctname
    ReportItemField
TotalField       -> Align -> [WideBuilder] -> Cell
Cell Align
align ([WideBuilder] -> Cell)
-> (WideBuilder -> [WideBuilder]) -> WideBuilder -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WideBuilder -> [WideBuilder]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WideBuilder -> Cell) -> WideBuilder -> Cell
forall a b. (a -> b) -> a -> b
$ AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
dopts MixedAmount
total
    ReportItemField
_                -> Align -> [WideBuilder] -> Cell
Cell Align
align [WideBuilder
forall a. Monoid a => a
mempty]
  where
    align :: Align
align | Bool
topaligned Bool -> Bool -> Bool
&& Bool
ljust = Align
TopLeft
          | Bool
topaligned          = Align
TopRight
          | Bool
ljust               = Align
BottomLeft
          | Bool
otherwise           = Align
BottomRight
    dopts :: AmountDisplayOpts
dopts = (Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts Bool
True ReportOpts
opts){displayOneLine :: Bool
displayOneLine=Bool
oneline, displayMinWidth :: Maybe Int
displayMinWidth=Maybe Int
mmin, displayMaxWidth :: Maybe Int
displayMaxWidth=Maybe Int
mmax}

-- rendering multi-column balance reports

-- | Render a multi-column balance report as CSV.
-- The CSV will always include the initial headings row,
-- and will include the final totals row unless --no-total is set.
multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV
multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV
multiBalanceReportAsCsv opts :: ReportOpts
opts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Costing
StringFormat
Period
Interval
commodity_column_ :: Bool
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
cost_ :: ReportOpts -> Costing
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe Text
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
commodity_column_ :: ReportOpts -> Bool
..} =
  (if Bool
transpose_ then CSV -> CSV
forall a. [[a]] -> [[a]]
transpose else CSV -> CSV
forall a. a -> a
id) (CSV -> CSV)
-> (MultiBalanceReport -> CSV) -> MultiBalanceReport -> CSV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CSV -> CSV -> CSV) -> (CSV, CSV) -> CSV
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry CSV -> CSV -> CSV
forall a. [a] -> [a] -> [a]
(++) ((CSV, CSV) -> CSV)
-> (MultiBalanceReport -> (CSV, CSV)) -> MultiBalanceReport -> CSV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> MultiBalanceReport -> (CSV, CSV)
multiBalanceReportAsCsv' ReportOpts
opts

multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV)
multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV)
multiBalanceReportAsCsv' opts :: ReportOpts
opts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Costing
StringFormat
Period
Interval
commodity_column_ :: Bool
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
cost_ :: ReportOpts -> Costing
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe Text
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
commodity_column_ :: ReportOpts -> Bool
..} (PeriodicReport [DateSpan]
colspans [PeriodicReportRow DisplayName MixedAmount]
items PeriodicReportRow () MixedAmount
tr) =
    ( (Text
"account" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text
"commodity" | Bool
commodity_column_] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (DateSpan -> Text) -> [DateSpan] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DateSpan -> Text
showDateSpan [DateSpan]
colspans
       [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"total"   | Bool
row_total_]
       [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"average" | Bool
average_]
      ) [Text] -> CSV -> CSV
forall a. a -> [a] -> [a]
: (PeriodicReportRow DisplayName MixedAmount -> CSV)
-> [PeriodicReportRow DisplayName MixedAmount] -> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((PeriodicReportRow DisplayName MixedAmount -> Text)
-> PeriodicReportRow DisplayName MixedAmount -> CSV
forall a.
(PeriodicReportRow a MixedAmount -> Text)
-> PeriodicReportRow a MixedAmount -> CSV
fullRowAsTexts (Int -> Text -> Text
accountNameDrop Int
drop_ (Text -> Text)
-> (PeriodicReportRow DisplayName MixedAmount -> Text)
-> PeriodicReportRow DisplayName MixedAmount
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicReportRow DisplayName MixedAmount -> Text
forall a. PeriodicReportRow DisplayName a -> Text
prrFullName)) [PeriodicReportRow DisplayName MixedAmount]
items
    , CSV
totalrows)
  where
    fullRowAsTexts :: (PeriodicReportRow a MixedAmount -> Text)
-> PeriodicReportRow a MixedAmount -> CSV
fullRowAsTexts PeriodicReportRow a MixedAmount -> Text
render PeriodicReportRow a MixedAmount
row = (PeriodicReportRow a MixedAmount -> Text
render PeriodicReportRow a MixedAmount
row Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:) ([Text] -> [Text]) -> CSV -> CSV
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReportOpts -> PeriodicReportRow a MixedAmount -> CSV
forall a. ReportOpts -> PeriodicReportRow a MixedAmount -> CSV
multiBalanceRowAsCsvText ReportOpts
opts PeriodicReportRow a MixedAmount
row
    totalrows :: CSV
totalrows
      | Bool
no_total_ = CSV
forall a. Monoid a => a
mempty
      | Bool
otherwise = (PeriodicReportRow () MixedAmount -> Text)
-> PeriodicReportRow () MixedAmount -> CSV
forall a.
(PeriodicReportRow a MixedAmount -> Text)
-> PeriodicReportRow a MixedAmount -> CSV
fullRowAsTexts (Text -> PeriodicReportRow () MixedAmount -> Text
forall a b. a -> b -> a
const Text
"total") PeriodicReportRow () MixedAmount
tr

-- | Render a multi-column balance report as HTML.
multiBalanceReportAsHtml :: ReportOpts -> MultiBalanceReport -> Html ()
multiBalanceReportAsHtml :: ReportOpts -> MultiBalanceReport -> Html ()
multiBalanceReportAsHtml ReportOpts
ropts MultiBalanceReport
mbr =
  let
    (Html ()
headingsrow,[Html ()]
bodyrows,[Html ()]
mtotalsrows) = ReportOpts -> MultiBalanceReport -> (Html (), [Html ()], [Html ()])
multiBalanceReportHtmlRows ReportOpts
ropts MultiBalanceReport
mbr
  in
    Html () -> Html ()
forall arg result. Term arg result => arg -> result
table_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Html ()] -> Html ()
forall a. Monoid a => [a] -> a
mconcat ([Html ()] -> Html ()) -> [Html ()] -> Html ()
forall a b. (a -> b) -> a -> b
$
         [Html ()
headingsrow]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
bodyrows
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
mtotalsrows

-- | Render the HTML table rows for a MultiBalanceReport.
-- Returns the heading row, 0 or more body rows, and the totals row if enabled.
multiBalanceReportHtmlRows :: ReportOpts -> MultiBalanceReport -> (Html (), [Html ()], [Html ()])
multiBalanceReportHtmlRows :: ReportOpts -> MultiBalanceReport -> (Html (), [Html ()], [Html ()])
multiBalanceReportHtmlRows ReportOpts
ropts MultiBalanceReport
mbr =
  let
    -- TODO: should the commodity_column be displayed as a subaccount in this case as well?
    ([Text]
headingsrow:CSV
bodyrows, CSV
mtotalsrows)
      | ReportOpts -> Bool
transpose_ ReportOpts
ropts = CommandDoc -> (CSV, CSV)
forall a. CommandDoc -> a
error' CommandDoc
"Sorry, --transpose with HTML output is not yet supported"  -- PARTIAL:
      | Bool
otherwise = ReportOpts -> MultiBalanceReport -> (CSV, CSV)
multiBalanceReportAsCsv' ReportOpts
ropts MultiBalanceReport
mbr
  in
    (ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlHeadRow ReportOpts
ropts [Text]
headingsrow
    ,([Text] -> Html ()) -> CSV -> [Html ()]
forall a b. (a -> b) -> [a] -> [b]
map (ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlBodyRow ReportOpts
ropts) CSV
bodyrows
    ,ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlFootRow ReportOpts
ropts ([Text] -> Html ()) -> CSV -> [Html ()]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CSV
mtotalsrows -- TODO pad totals row with zeros when there are
    )

-- | Render one MultiBalanceReport heading row as a HTML table row.
multiBalanceReportHtmlHeadRow :: ReportOpts -> [T.Text] -> Html ()
multiBalanceReportHtmlHeadRow :: ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlHeadRow ReportOpts
_ [] = Html ()
forall a. Monoid a => a
mempty  -- shouldn't happen
multiBalanceReportHtmlHeadRow ReportOpts
ropts (Text
acct:[Text]
rest) =
  let
    defstyle :: Attribute
defstyle = Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
""
    ([Text]
amts,[Text]
tot,[Text]
avg)
      | ReportOpts -> Bool
row_total_ ReportOpts
ropts Bool -> Bool -> Bool
&& ReportOpts -> Bool
average_ ReportOpts
ropts = ([Text] -> [Text]
forall a. [a] -> [a]
init ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest, [[Text] -> Text
forall a. [a] -> a
last ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest], [[Text] -> Text
forall a. [a] -> a
last [Text]
rest])
      | ReportOpts -> Bool
row_total_ ReportOpts
ropts                   = ([Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest,        [[Text] -> Text
forall a. [a] -> a
last [Text]
rest],        [])
      |                     ReportOpts -> Bool
average_ ReportOpts
ropts = ([Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest,        [],                 [[Text] -> Text
forall a. [a] -> a
last [Text]
rest])
      | Bool
otherwise                          = ([Text]
rest,             [],                 [])
  in
    Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Html ()] -> Html ()
forall a. Monoid a => [a] -> a
mconcat ([Html ()] -> Html ()) -> [Html ()] -> Html ()
forall a b. (a -> b) -> a -> b
$
          [Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"account"]              (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
acct)
       Html () -> [Html ()] -> [Html ()]
forall a. a -> [a] -> [a]
: [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"", Attribute
defstyle]           (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
amts]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"rowtotal", Attribute
defstyle]   (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
tot]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"rowaverage", Attribute
defstyle] (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
avg]

-- | Render one MultiBalanceReport data row as a HTML table row.
multiBalanceReportHtmlBodyRow :: ReportOpts -> [T.Text] -> Html ()
multiBalanceReportHtmlBodyRow :: ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlBodyRow ReportOpts
_ [] = Html ()
forall a. Monoid a => a
mempty  -- shouldn't happen
multiBalanceReportHtmlBodyRow ReportOpts
ropts (Text
label:[Text]
rest) =
  let
    defstyle :: Attribute
defstyle = Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:right"
    ([Text]
amts,[Text]
tot,[Text]
avg)
      | ReportOpts -> Bool
row_total_ ReportOpts
ropts Bool -> Bool -> Bool
&& ReportOpts -> Bool
average_ ReportOpts
ropts = ([Text] -> [Text]
forall a. [a] -> [a]
init ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest, [[Text] -> Text
forall a. [a] -> a
last ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest], [[Text] -> Text
forall a. [a] -> a
last [Text]
rest])
      | ReportOpts -> Bool
row_total_ ReportOpts
ropts                   = ([Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest,        [[Text] -> Text
forall a. [a] -> a
last [Text]
rest],        [])
      |                     ReportOpts -> Bool
average_ ReportOpts
ropts = ([Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest,        [],                 [[Text] -> Text
forall a. [a] -> a
last [Text]
rest])
      | Bool
otherwise                          = ([Text]
rest,             [],                 [])
  in
    Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Html ()] -> Html ()
forall a. Monoid a => [a] -> a
mconcat ([Html ()] -> Html ()) -> [Html ()] -> Html ()
forall a b. (a -> b) -> a -> b
$
          [Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"account", Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:left"]  (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
label)
       Html () -> [Html ()] -> [Html ()]
forall a. a -> [a] -> [a]
: [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"amount", Attribute
defstyle]            (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
amts]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"amount rowtotal", Attribute
defstyle]   (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
tot]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Text -> Attribute
class_ Text
"amount rowaverage", Attribute
defstyle] (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
avg]

-- | Render one MultiBalanceReport totals row as a HTML table row.
multiBalanceReportHtmlFootRow :: ReportOpts -> [T.Text] -> Html ()
multiBalanceReportHtmlFootRow :: ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlFootRow ReportOpts
_ropts [] = Html ()
forall a. Monoid a => a
mempty
-- TODO pad totals row with zeros when subreport is empty
--  multiBalanceReportHtmlFootRow ropts $
--     ""
--   : repeat nullmixedamt zeros
--  ++ (if row_total_ ropts then [nullmixedamt] else [])
--  ++ (if average_ ropts   then [nullmixedamt]   else [])
multiBalanceReportHtmlFootRow ReportOpts
ropts (Text
acct:[Text]
rest) =
  let
    defstyle :: Attribute
defstyle = Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:right"
    ([Text]
amts,[Text]
tot,[Text]
avg)
      | ReportOpts -> Bool
row_total_ ReportOpts
ropts Bool -> Bool -> Bool
&& ReportOpts -> Bool
average_ ReportOpts
ropts = ([Text] -> [Text]
forall a. [a] -> [a]
init ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest, [[Text] -> Text
forall a. [a] -> a
last ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest], [[Text] -> Text
forall a. [a] -> a
last [Text]
rest])
      | ReportOpts -> Bool
row_total_ ReportOpts
ropts                   = ([Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest,        [[Text] -> Text
forall a. [a] -> a
last [Text]
rest],        [])
      |                     ReportOpts -> Bool
average_ ReportOpts
ropts = ([Text] -> [Text]
forall a. [a] -> [a]
init [Text]
rest,        [],                 [[Text] -> Text
forall a. [a] -> a
last [Text]
rest])
      | Bool
otherwise                          = ([Text]
rest,             [],                 [])
  in
    Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Html ()] -> Html ()
forall a. Monoid a => [a] -> a
mconcat ([Html ()] -> Html ()) -> [Html ()] -> Html ()
forall a b. (a -> b) -> a -> b
$
          [Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:left"]             (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
acct)
       Html () -> [Html ()] -> [Html ()]
forall a. a -> [a] -> [a]
: [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Text -> Attribute
class_ Text
"amount coltotal", Attribute
defstyle]   (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
amts]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Text -> Attribute
class_ Text
"amount coltotal", Attribute
defstyle]   (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
tot]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Text -> Attribute
class_ Text
"amount colaverage", Attribute
defstyle] (Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
a) | Text
a <- [Text]
avg]

--thRow :: [String] -> Html ()
--thRow = tr_ . mconcat . map (th_ . toHtml)

-- | Render a multi-column balance report as plain text suitable for console output.
multiBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> TL.Text
multiBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> Text
multiBalanceReportAsText ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Costing
StringFormat
Period
Interval
commodity_column_ :: Bool
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
cost_ :: ReportOpts -> Costing
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe Text
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
commodity_column_ :: ReportOpts -> Bool
..} MultiBalanceReport
r = Builder -> Text
TB.toLazyText (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$
    Text -> Builder
TB.fromText Text
title
    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
TB.fromText Text
"\n\n"
    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ReportOpts -> Table Text Text WideBuilder -> Builder
balanceReportTableAsText ReportOpts
ropts (ReportOpts -> MultiBalanceReport -> Table Text Text WideBuilder
balanceReportAsTable ReportOpts
ropts MultiBalanceReport
r)
  where
    title :: Text
title = Text
mtitle Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" in " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DateSpan -> Text
showDateSpan (MultiBalanceReport -> DateSpan
forall a b. PeriodicReport a b -> DateSpan
periodicReportSpan MultiBalanceReport
r) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
valuationdesc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"

    mtitle :: Text
mtitle = case (BalanceCalculation
balancecalc_, BalanceAccumulation
balanceaccum_) of
        (BalanceCalculation
CalcValueChange, BalanceAccumulation
PerPeriod  ) -> Text
"Period-end value changes"
        (BalanceCalculation
CalcValueChange, BalanceAccumulation
Cumulative ) -> Text
"Cumulative period-end value changes"
        (BalanceCalculation
CalcGain,        BalanceAccumulation
PerPeriod  ) -> Text
"Incremental gain"
        (BalanceCalculation
CalcGain,        BalanceAccumulation
Cumulative ) -> Text
"Cumulative gain"
        (BalanceCalculation
CalcGain,        BalanceAccumulation
Historical ) -> Text
"Historical gain"
        (BalanceCalculation
_,               BalanceAccumulation
PerPeriod  ) -> Text
"Balance changes"
        (BalanceCalculation
_,               BalanceAccumulation
Cumulative ) -> Text
"Ending balances (cumulative)"
        (BalanceCalculation
_,               BalanceAccumulation
Historical)  -> Text
"Ending balances (historical)"
    valuationdesc :: Text
valuationdesc =
        (case Costing
cost_ of
            Costing
Cost   -> Text
", converted to cost"
            Costing
NoCost -> Text
"")
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (case Maybe ValuationType
value_ of
            Just (AtThen Maybe Text
_mc)    -> Text
", valued at posting date"
            Just (AtEnd Maybe Text
_mc) | Bool
changingValuation -> Text
""
            Just (AtEnd Maybe Text
_mc)     -> Text
", valued at period ends"
            Just (AtNow Maybe Text
_mc)     -> Text
", current value"
            Just (AtDate Day
d Maybe Text
_mc)  -> Text
", valued at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Day -> Text
showDate Day
d
            Maybe ValuationType
Nothing              -> Text
"")

    changingValuation :: Bool
changingValuation = case (BalanceCalculation
balancecalc_, BalanceAccumulation
balanceaccum_) of
        (BalanceCalculation
CalcValueChange, BalanceAccumulation
PerPeriod)  -> Bool
True
        (BalanceCalculation
CalcValueChange, BalanceAccumulation
Cumulative) -> Bool
True
        (BalanceCalculation, BalanceAccumulation)
_                                     -> Bool
False

-- | Build a 'Table' from a multi-column balance report.
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text WideBuilder
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table Text Text WideBuilder
balanceReportAsTable opts :: ReportOpts
opts@ReportOpts{Bool
average_ :: Bool
average_ :: ReportOpts -> Bool
average_, Bool
row_total_ :: Bool
row_total_ :: ReportOpts -> Bool
row_total_, BalanceAccumulation
balanceaccum_ :: BalanceAccumulation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
balanceaccum_}
    (PeriodicReport [DateSpan]
spans [PeriodicReportRow DisplayName MixedAmount]
items PeriodicReportRow () MixedAmount
tr) =
   Table Text Text WideBuilder -> Table Text Text WideBuilder
forall rh a. Table rh rh a -> Table rh rh a
maybetranspose (Table Text Text WideBuilder -> Table Text Text WideBuilder)
-> Table Text Text WideBuilder -> Table Text Text WideBuilder
forall a b. (a -> b) -> a -> b
$
   Table Text Text WideBuilder -> Table Text Text WideBuilder
forall ch. Table Text ch WideBuilder -> Table Text ch WideBuilder
addtotalrow (Table Text Text WideBuilder -> Table Text Text WideBuilder)
-> Table Text Text WideBuilder -> Table Text Text WideBuilder
forall a b. (a -> b) -> a -> b
$
   Header Text
-> Header Text -> [[WideBuilder]] -> Table Text Text WideBuilder
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table
     (Properties -> [Header Text] -> Header Text
forall h. Properties -> [Header h] -> Header h
Tab.Group Properties
NoLine ([Header Text] -> Header Text) -> [Header Text] -> Header Text
forall a b. (a -> b) -> a -> b
$ (Text -> Header Text) -> [Text] -> [Header Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Header Text
forall h. h -> Header h
Header (CSV -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat CSV
accts))
     (Properties -> [Header Text] -> Header Text
forall h. Properties -> [Header h] -> Header h
Tab.Group Properties
NoLine ([Header Text] -> Header Text) -> [Header Text] -> Header Text
forall a b. (a -> b) -> a -> b
$ (Text -> Header Text) -> [Text] -> [Header Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Header Text
forall h. h -> Header h
Header [Text]
colheadings)
     ([[[WideBuilder]]] -> [[WideBuilder]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[[WideBuilder]]]
rows)
  where
    totalscolumn :: Bool
totalscolumn = Bool
row_total_ Bool -> Bool -> Bool
&& BalanceAccumulation
balanceaccum_ BalanceAccumulation -> [BalanceAccumulation] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [BalanceAccumulation
Cumulative, BalanceAccumulation
Historical]
    colheadings :: [Text]
colheadings = [Text
"Commodity" | ReportOpts -> Bool
commodity_column_ ReportOpts
opts]
                  [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (DateSpan -> Text) -> [DateSpan] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (BalanceAccumulation -> [DateSpan] -> DateSpan -> Text
reportPeriodName BalanceAccumulation
balanceaccum_ [DateSpan]
spans) [DateSpan]
spans
                  [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"  Total" | Bool
totalscolumn]
                  [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"Average" | Bool
average_]
    fullRowAsTexts :: PeriodicReportRow DisplayName MixedAmount
-> ([Text], [[WideBuilder]])
fullRowAsTexts PeriodicReportRow DisplayName MixedAmount
row =
      let rs :: [[WideBuilder]]
rs = ReportOpts
-> PeriodicReportRow DisplayName MixedAmount -> [[WideBuilder]]
forall a.
ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsTableText ReportOpts
opts PeriodicReportRow DisplayName MixedAmount
row
       in (Int -> Text -> [Text]
forall a. Int -> a -> [a]
replicate ([[WideBuilder]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[WideBuilder]]
rs) (PeriodicReportRow DisplayName MixedAmount -> Text
forall a. PeriodicReportRow DisplayName a -> Text
renderacct PeriodicReportRow DisplayName MixedAmount
row), [[WideBuilder]]
rs)
    (CSV
accts, [[[WideBuilder]]]
rows) = [([Text], [[WideBuilder]])] -> (CSV, [[[WideBuilder]]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([([Text], [[WideBuilder]])] -> (CSV, [[[WideBuilder]]]))
-> [([Text], [[WideBuilder]])] -> (CSV, [[[WideBuilder]]])
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName MixedAmount
 -> ([Text], [[WideBuilder]]))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [([Text], [[WideBuilder]])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PeriodicReportRow DisplayName MixedAmount
-> ([Text], [[WideBuilder]])
fullRowAsTexts [PeriodicReportRow DisplayName MixedAmount]
items
    renderacct :: PeriodicReportRow DisplayName a -> Text
renderacct PeriodicReportRow DisplayName a
row =
        Int -> Text -> Text
T.replicate ((PeriodicReportRow DisplayName a -> Int
forall a. PeriodicReportRow DisplayName a -> Int
prrDepth PeriodicReportRow DisplayName a
row Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> PeriodicReportRow DisplayName a -> Text
forall a. PeriodicReportRow DisplayName a -> Text
prrDisplayName PeriodicReportRow DisplayName a
row
    addtotalrow :: Table Text ch WideBuilder -> Table Text ch WideBuilder
addtotalrow
      | ReportOpts -> Bool
no_total_ ReportOpts
opts = Table Text ch WideBuilder -> Table Text ch WideBuilder
forall a. a -> a
id
      | Bool
otherwise =
        let totalrows :: [[WideBuilder]]
totalrows = ReportOpts -> PeriodicReportRow () MixedAmount -> [[WideBuilder]]
forall a.
ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsTableText ReportOpts
opts PeriodicReportRow () MixedAmount
tr
            rh :: Header Text
rh = Properties -> [Header Text] -> Header Text
forall h. Properties -> [Header h] -> Header h
Tab.Group Properties
NoLine ([Header Text] -> Header Text)
-> (Header Text -> [Header Text]) -> Header Text -> Header Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Header Text -> [Header Text]
forall a. Int -> a -> [a]
replicate ([[WideBuilder]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[WideBuilder]]
totalrows) (Header Text -> Header Text) -> Header Text -> Header Text
forall a b. (a -> b) -> a -> b
$ Text -> Header Text
forall h. h -> Header h
Header Text
""
            ch :: Header [a]
ch = [a] -> Header [a]
forall h. h -> Header h
Header [] -- ignored
         in ((Table Text ch WideBuilder
 -> Table Text [Any] WideBuilder -> Table Text ch WideBuilder)
-> Table Text [Any] WideBuilder
-> Table Text ch WideBuilder
-> Table Text ch WideBuilder
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Properties
-> Table Text ch WideBuilder
-> Table Text [Any] WideBuilder
-> Table Text ch WideBuilder
forall rh ch a ch2.
Properties -> Table rh ch a -> Table rh ch2 a -> Table rh ch a
concatTables Properties
SingleLine) (Table Text [Any] WideBuilder
 -> Table Text ch WideBuilder -> Table Text ch WideBuilder)
-> Table Text [Any] WideBuilder
-> Table Text ch WideBuilder
-> Table Text ch WideBuilder
forall a b. (a -> b) -> a -> b
$ Header Text
-> Header [Any] -> [[WideBuilder]] -> Table Text [Any] WideBuilder
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table Header Text
rh Header [Any]
forall a. Header [a]
ch [[WideBuilder]]
totalrows)
    maybetranspose :: Table rh rh a -> Table rh rh a
maybetranspose | ReportOpts -> Bool
transpose_ ReportOpts
opts = \(Table Header rh
rh Header rh
ch [[a]]
vals) -> Header rh -> Header rh -> [[a]] -> Table rh rh a
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table Header rh
ch Header rh
rh ([[a]] -> [[a]]
forall a. [[a]] -> [[a]]
transpose [[a]]
vals)
                   | Bool
otherwise       = Table rh rh a -> Table rh rh a
forall a. a -> a
id

multiBalanceRowAsWbs :: AmountDisplayOpts -> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsWbs :: AmountDisplayOpts
-> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsWbs AmountDisplayOpts
bopts ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Costing
StringFormat
Period
Interval
commodity_column_ :: Bool
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
cost_ :: ReportOpts -> Costing
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe Text
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
commodity_column_ :: ReportOpts -> Bool
..} (PeriodicReportRow a
_ [MixedAmount]
as MixedAmount
rowtot MixedAmount
rowavg)
  | Bool -> Bool
not Bool
commodity_column_ = [(MixedAmount -> WideBuilder) -> [MixedAmount] -> [WideBuilder]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
bopts) [MixedAmount]
all]
  | Bool
otherwise =
        (WideBuilder -> [WideBuilder] -> [WideBuilder])
-> [WideBuilder] -> [[WideBuilder]] -> [[WideBuilder]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (:) ((Text -> WideBuilder) -> [Text] -> [WideBuilder]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> WideBuilder
wbFromText [Text]
cs)  -- add symbols
      ([[WideBuilder]] -> [[WideBuilder]])
-> ([MixedAmount] -> [[WideBuilder]])
-> [MixedAmount]
-> [[WideBuilder]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[WideBuilder]] -> [[WideBuilder]]
forall a. [[a]] -> [[a]]
transpose                         -- each row becomes a list of Text quantities
      ([[WideBuilder]] -> [[WideBuilder]])
-> ([MixedAmount] -> [[WideBuilder]])
-> [MixedAmount]
-> [[WideBuilder]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MixedAmount -> [WideBuilder]) -> [MixedAmount] -> [[WideBuilder]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AmountDisplayOpts -> MixedAmount -> [WideBuilder]
showMixedAmountLinesB AmountDisplayOpts
bopts{displayOrder :: Maybe [Text]
displayOrder=[Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
cs, displayMinWidth :: Maybe Int
displayMinWidth=Maybe Int
forall a. Maybe a
Nothing})
      ([MixedAmount] -> [[WideBuilder]])
-> [MixedAmount] -> [[WideBuilder]]
forall a b. (a -> b) -> a -> b
$ [MixedAmount]
all
  where
    totalscolumn :: Bool
totalscolumn = Bool
row_total_ Bool -> Bool -> Bool
&& BalanceAccumulation
balanceaccum_ BalanceAccumulation -> [BalanceAccumulation] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [BalanceAccumulation
Cumulative, BalanceAccumulation
Historical]
    cs :: [Text]
cs = Set Text -> [Text]
forall a. Set a -> [a]
S.toList (Set Text -> [Text])
-> ([Set Text] -> Set Text) -> [Set Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Set Text -> Set Text -> Set Text)
-> Set Text -> [Set Text] -> Set Text
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Set Text -> Set Text -> Set Text
forall a. Ord a => Set a -> Set a -> Set a
S.union Set Text
forall a. Monoid a => a
mempty ([Set Text] -> [Text]) -> [Set Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (MixedAmount -> Set Text) -> [MixedAmount] -> [Set Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MixedAmount -> Set Text
maCommodities [MixedAmount]
all
    all :: [MixedAmount]
all = [MixedAmount]
as
        [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ [MixedAmount
rowtot | Bool
totalscolumn Bool -> Bool -> Bool
&& Bool -> Bool
not ([MixedAmount] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MixedAmount]
as)]
        [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ [MixedAmount
rowavg | Bool
average_     Bool -> Bool -> Bool
&& Bool -> Bool
not ([MixedAmount] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MixedAmount]
as)]

multiBalanceRowAsCsvText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[T.Text]]
multiBalanceRowAsCsvText :: ReportOpts -> PeriodicReportRow a MixedAmount -> CSV
multiBalanceRowAsCsvText ReportOpts
opts = ([WideBuilder] -> [Text]) -> [[WideBuilder]] -> CSV
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((WideBuilder -> Text) -> [WideBuilder] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WideBuilder -> Text
wbToText) ([[WideBuilder]] -> CSV)
-> (PeriodicReportRow a MixedAmount -> [[WideBuilder]])
-> PeriodicReportRow a MixedAmount
-> CSV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AmountDisplayOpts
-> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
forall a.
AmountDisplayOpts
-> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsWbs (Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts Bool
False ReportOpts
opts) ReportOpts
opts

multiBalanceRowAsTableText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsTableText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsTableText ReportOpts
opts = AmountDisplayOpts
-> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
forall a.
AmountDisplayOpts
-> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsWbs (Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts Bool
True ReportOpts
opts) ReportOpts
opts

-- | Amount display options to use for balance reports
balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts
balanceOpts Bool
isTable ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Costing
StringFormat
Period
Interval
commodity_column_ :: Bool
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
cost_ :: ReportOpts -> Costing
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe Text
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
commodity_column_ :: ReportOpts -> Bool
..} = AmountDisplayOpts
oneLine
    { displayColour :: Bool
displayColour   = Bool
isTable Bool -> Bool -> Bool
&& Bool
color_
    , displayMaxWidth :: Maybe Int
displayMaxWidth = if Bool
isTable Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
no_elide_ then Int -> Maybe Int
forall a. a -> Maybe a
Just Int
32 else Maybe Int
forall a. Maybe a
Nothing
    }

tests_Balance :: TestTree
tests_Balance = CommandDoc -> [TestTree] -> TestTree
testGroup CommandDoc
"Balance" [

   CommandDoc -> [TestTree] -> TestTree
testGroup CommandDoc
"balanceReportAsText" [
    CommandDoc -> IO () -> TestTree
testCase CommandDoc
"unicode in balance layout" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$ do
      Journal
j <- Text -> IO Journal
readJournal' Text
"2009/01/01 * медвежья шкура\n  расходы:покупки  100\n  актив:наличные\n"
      let rspec :: ReportSpec
rspec = ReportSpec
defreportspec{_rsReportOpts :: ReportOpts
_rsReportOpts=ReportOpts
defreportopts{no_total_ :: Bool
no_total_=Bool
True}}
      Builder -> Text
TB.toLazyText (ReportOpts -> BalanceReport -> Builder
balanceReportAsText (ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec) (ReportSpec -> Journal -> BalanceReport
balanceReport ReportSpec
rspec{_rsDay :: Day
_rsDay=Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
11 Int
26} Journal
j))
        Text -> Text -> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?=
        [Text] -> Text
TL.unlines
        [Text
"                -100  актив:наличные"
        ,Text
"                 100  расходы:покупки"
        ]
    ]

  ]