{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-|

Common helpers for making multi-section balance report commands
like balancesheet, cashflow, and incomestatement.

-}

module Hledger.Cli.CompoundBalanceCommand (
  CompoundBalanceCommandSpec(..)
 ,compoundBalanceCommandMode
 ,compoundBalanceCommand
) where

import Data.List (foldl')
import Data.Maybe (fromMaybe, mapMaybe)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Data.Time.Calendar (Day, addDays)
import System.Console.CmdArgs.Explicit as C
import Hledger.Read.CsvReader (CSV, printCSV)
import Lucid as L hiding (value_)
import Text.Tabular.AsciiWide as Tab

import Hledger
import Hledger.Cli.Commands.Balance
import Hledger.Cli.CliOptions
import Hledger.Cli.Utils (unsupportedOutputFormatError, writeOutputLazyText)

-- | Description of a compound balance report command,
-- from which we generate the command's cmdargs mode and IO action.
-- A compound balance report command shows one or more sections/subreports,
-- each with its own title and subtotals row, in a certain order,
-- plus a grand totals row if there's more than one section.
-- Examples are the balancesheet, cashflow and incomestatement commands.
--
-- Compound balance reports do sign normalisation: they show all account balances
-- as normally positive, unlike the ordinary BalanceReport and most hledger commands
-- which show income/liability/equity balances as normally negative.
-- Each subreport specifies the normal sign of its amounts, and whether
-- it should be added to or subtracted from the grand total.
--
data CompoundBalanceCommandSpec = CompoundBalanceCommandSpec {
  CompoundBalanceCommandSpec -> CommandDoc
cbcdoc      :: CommandDoc,                      -- ^ the command's name(s) and documentation
  CompoundBalanceCommandSpec -> CommandDoc
cbctitle    :: String,                          -- ^ overall report title
  CompoundBalanceCommandSpec -> [CBCSubreportSpec DisplayName]
cbcqueries  :: [CBCSubreportSpec DisplayName],  -- ^ subreport details
  CompoundBalanceCommandSpec -> BalanceAccumulation
cbcaccum    :: BalanceAccumulation              -- ^ how to accumulate balances (per-period, cumulative, historical)
                                                  --   (overrides command line flags)
}

-- | Generate a cmdargs option-parsing mode from a compound balance command
-- specification.
compoundBalanceCommandMode :: CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode :: CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode CompoundBalanceCommandSpec{CommandDoc
[CBCSubreportSpec DisplayName]
BalanceAccumulation
cbcaccum :: BalanceAccumulation
cbcqueries :: [CBCSubreportSpec DisplayName]
cbctitle :: CommandDoc
cbcdoc :: CommandDoc
cbcaccum :: CompoundBalanceCommandSpec -> BalanceAccumulation
cbcqueries :: CompoundBalanceCommandSpec -> [CBCSubreportSpec DisplayName]
cbctitle :: CompoundBalanceCommandSpec -> CommandDoc
cbcdoc :: CompoundBalanceCommandSpec -> CommandDoc
..} =
  CommandDoc
-> [Flag RawOpts]
-> [(CommandDoc, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
   CommandDoc
cbcdoc
   ([[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)"
   ,[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 period-end historical balance value (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
"budget"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"budget")
      CommandDoc
"show sum of posting amounts compared to budget goals defined by periodic transactions\n "

   ,[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)"
           CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ BalanceAccumulation -> CommandDoc
defaultMarker BalanceAccumulation
PerPeriod)
    ,[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 -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ BalanceAccumulation -> CommandDoc
defaultMarker BalanceAccumulation
Cumulative)
    ,[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)"
           CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ BalanceAccumulation -> CommandDoc
defaultMarker BalanceAccumulation
Historical CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
"\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
"flat mode: omit N leading account name parts"
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"declared"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"declared") CommandDoc
"include non-parent declared accounts (best used with -E)"
    ,[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)"
    ,[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"
    ,[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]
-> Update RawOpts -> CommandDoc -> CommandDoc -> Flag RawOpts
forall a.
[CommandDoc] -> Update a -> CommandDoc -> CommandDoc -> Flag a
flagReq  [CommandDoc
"layout"] (\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
"layout" CommandDoc
s RawOpts
opts) CommandDoc
"ARG"
      ([CommandDoc] -> CommandDoc
unlines
        [CommandDoc
"how to show multi-commodity amounts:"
        ,CommandDoc
"'wide[,WIDTH]': all commodities on one line"
        ,CommandDoc
"'tall'        : each commodity on a new line"
        ,CommandDoc
"'bare'        : bare numbers, symbols in a column"
        ])
    ,[CommandDoc] -> Flag RawOpts
outputFormatFlag [CommandDoc
"txt",CommandDoc
"html",CommandDoc
"csv",CommandDoc
"json"]
    ,Flag RawOpts
outputFileFlag
    ])
    [(CommandDoc, [Flag RawOpts])
generalflagsgroup1]
    ([Flag RawOpts]
hiddenflags [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. [a] -> [a] -> [a]
++
      [ [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"
      ])
    ([], 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]")
 where
   defaultMarker :: BalanceAccumulation -> String
   defaultMarker :: BalanceAccumulation -> CommandDoc
defaultMarker BalanceAccumulation
bacc | BalanceAccumulation
bacc BalanceAccumulation -> BalanceAccumulation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceAccumulation
cbcaccum = CommandDoc
" (default)"
                      | Bool
otherwise        = CommandDoc
""

-- | Generate a runnable command from a compound balance command specification.
compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> IO ())
compoundBalanceCommand :: CompoundBalanceCommandSpec -> CliOpts -> Journal -> IO ()
compoundBalanceCommand CompoundBalanceCommandSpec{CommandDoc
[CBCSubreportSpec DisplayName]
BalanceAccumulation
cbcaccum :: BalanceAccumulation
cbcqueries :: [CBCSubreportSpec DisplayName]
cbctitle :: CommandDoc
cbcdoc :: CommandDoc
cbcaccum :: CompoundBalanceCommandSpec -> BalanceAccumulation
cbcqueries :: CompoundBalanceCommandSpec -> [CBCSubreportSpec DisplayName]
cbctitle :: CompoundBalanceCommandSpec -> CommandDoc
cbcdoc :: CompoundBalanceCommandSpec -> CommandDoc
..} opts :: CliOpts
opts@CliOpts{reportspec_ :: CliOpts -> ReportSpec
reportspec_=ReportSpec
rspec, rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts} Journal
j = do
    CliOpts -> Text -> IO ()
writeOutputLazyText CliOpts
opts (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ CompoundPeriodicReport DisplayName MixedAmount -> Text
render CompoundPeriodicReport DisplayName MixedAmount
cbr
  where
    ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe ConversionOp
Maybe ValuationType
Maybe NormalSign
BalanceCalculation
BalanceAccumulation
AccountListMode
Layout
StringFormat
Period
Interval
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
conversionop_ :: ReportOpts -> Maybe ConversionOp
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
declared_ :: ReportOpts -> Bool
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
layout_ :: ReportOpts -> Layout
layout_ :: Layout
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
declared_ :: 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
conversionop_ :: Maybe ConversionOp
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
..} = ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec
    -- use the default balance type for this report, unless the user overrides
    mbalanceAccumulationOverride :: Maybe BalanceAccumulation
mbalanceAccumulationOverride = RawOpts -> Maybe BalanceAccumulation
balanceAccumulationOverride RawOpts
rawopts
    balanceaccumulation :: BalanceAccumulation
balanceaccumulation = BalanceAccumulation
-> Maybe BalanceAccumulation -> BalanceAccumulation
forall a. a -> Maybe a -> a
fromMaybe BalanceAccumulation
cbcaccum Maybe BalanceAccumulation
mbalanceAccumulationOverride
    -- Set balance type in the report options.
    ropts' :: ReportOpts
ropts' = ReportOpts
ropts{balanceaccum_ :: BalanceAccumulation
balanceaccum_=BalanceAccumulation
balanceaccumulation}

    title :: Text
title =
      CommandDoc -> Text
T.pack CommandDoc
cbctitle
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" "
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
titledatestr
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (Text
" "Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) Maybe Text
mtitleclarification
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
valuationdesc
      where

        -- XXX #1078 the title of ending balance reports
        -- (Historical) should mention the end date(s) shown as
        -- column heading(s) (not the date span of the transactions).
        -- Also the dates should not be simplified (it should show
        -- "2008/01/01-2008/12/31", not "2008").
        titledatestr :: Text
titledatestr = case BalanceAccumulation
balanceaccumulation of
            BalanceAccumulation
Historical -> [Day] -> Text
showEndDates [Day]
enddates
            BalanceAccumulation
_          -> DateSpan -> Text
showDateSpan DateSpan
requestedspan
          where
            enddates :: [Day]
enddates = (Day -> Day) -> [Day] -> [Day]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> Day -> Day
addDays (-Integer
1)) ([Day] -> [Day]) -> ([DateSpan] -> [Day]) -> [DateSpan] -> [Day]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DateSpan -> Maybe Day) -> [DateSpan] -> [Day]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DateSpan -> Maybe Day
spanEnd ([DateSpan] -> [Day]) -> [DateSpan] -> [Day]
forall a b. (a -> b) -> a -> b
$ CompoundPeriodicReport DisplayName MixedAmount -> [DateSpan]
forall a b. CompoundPeriodicReport a b -> [DateSpan]
cbrDates CompoundPeriodicReport DisplayName MixedAmount
cbr  -- these spans will always have a definite end date
            requestedspan :: DateSpan
requestedspan = (DateSpan, [DateSpan]) -> DateSpan
forall a b. (a, b) -> a
fst ((DateSpan, [DateSpan]) -> DateSpan)
-> (DateSpan, [DateSpan]) -> DateSpan
forall a b. (a -> b) -> a -> b
$ Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan Journal
j ReportSpec
rspec

        -- when user overrides, add an indication to the report title
        -- Do we need to deal with overridden BalanceCalculation?
        mtitleclarification :: Maybe Text
mtitleclarification = case (BalanceCalculation
balancecalc_, BalanceAccumulation
balanceaccumulation, Maybe BalanceAccumulation
mbalanceAccumulationOverride) of
            (BalanceCalculation
CalcValueChange, BalanceAccumulation
PerPeriod,  Maybe BalanceAccumulation
_              ) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Period-End Value Changes)"
            (BalanceCalculation
CalcValueChange, BalanceAccumulation
Cumulative, Maybe BalanceAccumulation
_              ) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Cumulative Period-End Value Changes)"
            (BalanceCalculation
CalcGain,        BalanceAccumulation
PerPeriod,  Maybe BalanceAccumulation
_              ) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Incremental Gain)"
            (BalanceCalculation
CalcGain,        BalanceAccumulation
Cumulative, Maybe BalanceAccumulation
_              ) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Cumulative Gain)"
            (BalanceCalculation
CalcGain,        BalanceAccumulation
Historical, Maybe BalanceAccumulation
_              ) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Historical Gain)"
            (BalanceCalculation
_,               BalanceAccumulation
_,          Just BalanceAccumulation
PerPeriod ) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Balance Changes)"
            (BalanceCalculation
_,               BalanceAccumulation
_,          Just BalanceAccumulation
Cumulative) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Cumulative Ending Balances)"
            (BalanceCalculation
_,               BalanceAccumulation
_,          Just BalanceAccumulation
Historical) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"(Historical Ending Balances)"
            (BalanceCalculation, BalanceAccumulation,
 Maybe BalanceAccumulation)
_                                              -> Maybe Text
forall a. Maybe a
Nothing

        valuationdesc :: Text
valuationdesc =
          (case Maybe ConversionOp
conversionop_ of
               Just ConversionOp
ToCost -> Text
", converted to cost"
               Maybe ConversionOp
_           -> 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
today Maybe Text
_mc) -> Text
", valued at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Day -> Text
showDate Day
today
               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

    -- make a CompoundBalanceReport.
    cbr' :: CompoundPeriodicReport DisplayName MixedAmount
cbr' = ReportSpec
-> Journal
-> [CBCSubreportSpec DisplayName]
-> CompoundPeriodicReport DisplayName MixedAmount
forall a.
ReportSpec
-> Journal
-> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReport ReportSpec
rspec{_rsReportOpts :: ReportOpts
_rsReportOpts=ReportOpts
ropts'} Journal
j [CBCSubreportSpec DisplayName]
cbcqueries
    cbr :: CompoundPeriodicReport DisplayName MixedAmount
cbr  = CompoundPeriodicReport DisplayName MixedAmount
cbr'{cbrTitle :: Text
cbrTitle=Text
title}

    -- render appropriately
    render :: CompoundPeriodicReport DisplayName MixedAmount -> Text
render = case CliOpts -> CommandDoc
outputFormatFromOpts CliOpts
opts of
        CommandDoc
"txt"  -> ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> Text
compoundBalanceReportAsText ReportOpts
ropts'
        CommandDoc
"csv"  -> CSV -> Text
printCSV (CSV -> Text)
-> (CompoundPeriodicReport DisplayName MixedAmount -> CSV)
-> CompoundPeriodicReport DisplayName MixedAmount
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV
compoundBalanceReportAsCsv ReportOpts
ropts'
        CommandDoc
"html" -> Html () -> Text
forall a. Html a -> Text
L.renderText (Html () -> Text)
-> (CompoundPeriodicReport DisplayName MixedAmount -> Html ())
-> CompoundPeriodicReport DisplayName MixedAmount
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> Html ()
compoundBalanceReportAsHtml ReportOpts
ropts'
        CommandDoc
"json" -> CompoundPeriodicReport DisplayName MixedAmount -> Text
forall a. ToJSON a => a -> Text
toJsonText
        CommandDoc
x      -> CommandDoc
-> CompoundPeriodicReport DisplayName MixedAmount -> Text
forall a. CommandDoc -> a
error' (CommandDoc
 -> CompoundPeriodicReport DisplayName MixedAmount -> Text)
-> CommandDoc
-> CompoundPeriodicReport DisplayName MixedAmount
-> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
unsupportedOutputFormatError CommandDoc
x

-- | Summarise one or more (inclusive) end dates, in a way that's
-- visually different from showDateSpan, suggesting discrete end dates
-- rather than a continuous span.
showEndDates :: [Day] -> T.Text
showEndDates :: [Day] -> Text
showEndDates [Day]
es = case [Day]
es of
  -- cf showPeriod
  (Day
e:Day
_:[Day]
_) -> Day -> Text
showDate Day
e Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
".." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Day -> Text
showDate ([Day] -> Day
forall a. [a] -> a
last [Day]
es)
  [Day
e]     -> Day -> Text
showDate Day
e
  []      -> Text
""

-- | Render a compound balance report as plain text suitable for console output.
{- Eg:
Balance Sheet

             ||  2017/12/31    Total  Average
=============++===============================
 Assets      ||
-------------++-------------------------------
 assets:b    ||           1        1        1
-------------++-------------------------------
             ||           1        1        1
=============++===============================
 Liabilities ||
-------------++-------------------------------
-------------++-------------------------------
             ||
=============++===============================
 Total       ||           1        1        1

-}
compoundBalanceReportAsText :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> TL.Text
compoundBalanceReportAsText :: ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> Text
compoundBalanceReportAsText ReportOpts
ropts
  (CompoundPeriodicReport Text
title [DateSpan]
_colspans [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports PeriodicReportRow () MixedAmount
netrow) =
    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 Table Text Text WideBuilder
bigtable'
  where
    bigtable :: Table Text Text WideBuilder
bigtable =
      case ((Text, PeriodicReport DisplayName MixedAmount, Bool)
 -> Table Text Text WideBuilder)
-> [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
-> [Table Text Text WideBuilder]
forall a b. (a -> b) -> [a] -> [b]
map (ReportOpts
-> (Text, PeriodicReport DisplayName MixedAmount, Bool)
-> Table Text Text WideBuilder
forall c.
ReportOpts
-> (Text, PeriodicReport DisplayName MixedAmount, c)
-> Table Text Text WideBuilder
subreportAsTable ReportOpts
ropts) [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports of
        []   -> Table Text Text WideBuilder
forall rh ch a. Table rh ch a
Tab.empty
        Table Text Text WideBuilder
r:[Table Text Text WideBuilder]
rs -> (Table Text Text WideBuilder
 -> Table Text Text WideBuilder -> Table Text Text WideBuilder)
-> Table Text Text WideBuilder
-> [Table Text Text WideBuilder]
-> Table Text Text WideBuilder
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Properties
-> Table Text Text WideBuilder
-> Table Text Text WideBuilder
-> Table Text Text WideBuilder
forall rh ch a ch2.
Properties -> Table rh ch a -> Table rh ch2 a -> Table rh ch a
concatTables Properties
DoubleLine) Table Text Text WideBuilder
r [Table Text Text WideBuilder]
rs
    bigtable' :: Table Text Text WideBuilder
bigtable'
      | ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(Text, PeriodicReport DisplayName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 =
          Table Text Text WideBuilder
bigtable
      | Bool
otherwise =
        let totalrows :: [[WideBuilder]]
totalrows = ReportOpts -> PeriodicReportRow () MixedAmount -> [[WideBuilder]]
forall a.
ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
multiBalanceRowAsTableText ReportOpts
ropts PeriodicReportRow () MixedAmount
netrow
            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
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
"Net:" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Int -> Text -> [Text]
forall a. Int -> a -> [a]
replicate ([[WideBuilder]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[WideBuilder]]
totalrows Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Text
"")
            ch :: Header [a]
ch = [a] -> Header [a]
forall h. h -> Header h
Header [] -- ignored
         in ((Properties
-> Table Text Text WideBuilder
-> Table Text [Any] WideBuilder
-> Table Text Text WideBuilder
forall rh ch a ch2.
Properties -> Table rh ch a -> Table rh ch2 a -> Table rh ch a
concatTables Properties
Tab.DoubleLine) Table Text Text WideBuilder
bigtable (Table Text [Any] WideBuilder -> Table Text Text WideBuilder)
-> Table Text [Any] WideBuilder -> Table Text Text 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)

    -- | Convert a named multi balance report to a table suitable for
    -- concatenating with others to make a compound balance report table.
    subreportAsTable :: ReportOpts
-> (Text, PeriodicReport DisplayName MixedAmount, c)
-> Table Text Text WideBuilder
subreportAsTable ReportOpts
ropts (Text
title, PeriodicReport DisplayName MixedAmount
r, c
_) = Table Text Text WideBuilder
t
      where
        -- convert to table
        Table Header Text
lefthdrs Header Text
tophdrs [[WideBuilder]]
cells = ReportOpts
-> PeriodicReport DisplayName MixedAmount
-> Table Text Text WideBuilder
balanceReportAsTable ReportOpts
ropts PeriodicReport DisplayName MixedAmount
r
        -- tweak the layout
        t :: Table Text Text WideBuilder
t = 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
Tab.SingleLine [Text -> Header Text
forall h. h -> Header h
Tab.Header Text
title, Header Text
lefthdrs]) Header Text
tophdrs ([][WideBuilder] -> [[WideBuilder]] -> [[WideBuilder]]
forall a. a -> [a] -> [a]
:[[WideBuilder]]
cells)

-- | Render a compound balance report as CSV.
-- Subreports' CSV is concatenated, with the headings rows replaced by a
-- subreport title row, and an overall title row, one headings row, and an
-- optional overall totals row is added.
compoundBalanceReportAsCsv :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV
compoundBalanceReportAsCsv :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV
compoundBalanceReportAsCsv ReportOpts
ropts (CompoundPeriodicReport Text
title [DateSpan]
colspans [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports PeriodicReportRow () MixedAmount
netrow) =
    CSV -> CSV
addtotals (CSV -> CSV) -> CSV -> CSV
forall a b. (a -> b) -> a -> b
$
      Text -> [Text]
forall a. IsString a => a -> [a]
padRow Text
title
      [Text] -> CSV -> CSV
forall a. a -> [a] -> [a]
: ( Text
"Account"
        Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text
"Commodity" | ReportOpts -> Layout
layout_ ReportOpts
ropts Layout -> Layout -> Bool
forall a. Eq a => a -> a -> Bool
== Layout
LayoutBare]
        [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 (ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts) [DateSpan]
colspans) [DateSpan]
colspans
        [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [Text
"Total"] else [])
        [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts then [Text
"Average"] else [])
        )
      [Text] -> CSV -> CSV
forall a. a -> [a] -> [a]
: ((Text, PeriodicReport DisplayName MixedAmount, Bool) -> CSV)
-> [(Text, PeriodicReport DisplayName MixedAmount, Bool)] -> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ReportOpts
-> (Text, PeriodicReport DisplayName MixedAmount, Bool) -> CSV
forall c.
ReportOpts
-> (Text, PeriodicReport DisplayName MixedAmount, c) -> CSV
subreportAsCsv ReportOpts
ropts) [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports
  where
    -- | Add a subreport title row and drop the heading row.
    subreportAsCsv :: ReportOpts
-> (Text, PeriodicReport DisplayName MixedAmount, c) -> CSV
subreportAsCsv ReportOpts
ropts (Text
subreporttitle, PeriodicReport DisplayName MixedAmount
multibalreport, c
_) =
      Text -> [Text]
forall a. IsString a => a -> [a]
padRow Text
subreporttitle [Text] -> CSV -> CSV
forall a. a -> [a] -> [a]
:
      CSV -> CSV
forall a. [a] -> [a]
tail (ReportOpts -> PeriodicReport DisplayName MixedAmount -> CSV
multiBalanceReportAsCsv ReportOpts
ropts PeriodicReport DisplayName MixedAmount
multibalreport)
    padRow :: a -> [a]
padRow a
s = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
numcols ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ a
s a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a -> [a]
forall a. a -> [a]
repeat a
""
      where
        numcols :: Int
numcols
          | [(Text, PeriodicReport DisplayName MixedAmount, Bool)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports = Int
1
          | Bool
otherwise =
            (Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ -- account name column
            (if ReportOpts -> Layout
layout_ ReportOpts
ropts Layout -> Layout -> Bool
forall a. Eq a => a -> a -> Bool
== Layout
LayoutBare then (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+) else Int -> Int
forall a. a -> a
id) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
            (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+) else Int -> Int
forall a. a -> a
id) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
            (if ReportOpts -> Bool
average_ ReportOpts
ropts then (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+) else Int -> Int
forall a. a -> a
id) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
            [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ -- depends on non-null subreports
            ((Text, PeriodicReport DisplayName MixedAmount, Bool) -> Int)
-> [(Text, PeriodicReport DisplayName MixedAmount, Bool)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([DateSpan] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([DateSpan] -> Int)
-> ((Text, PeriodicReport DisplayName MixedAmount, Bool)
    -> [DateSpan])
-> (Text, PeriodicReport DisplayName MixedAmount, Bool)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicReport DisplayName MixedAmount -> [DateSpan]
forall a b. PeriodicReport a b -> [DateSpan]
prDates (PeriodicReport DisplayName MixedAmount -> [DateSpan])
-> ((Text, PeriodicReport DisplayName MixedAmount, Bool)
    -> PeriodicReport DisplayName MixedAmount)
-> (Text, PeriodicReport DisplayName MixedAmount, Bool)
-> [DateSpan]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, PeriodicReport DisplayName MixedAmount, Bool)
-> PeriodicReport DisplayName MixedAmount
forall a b c. (a, b, c) -> b
second3) [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports
    addtotals :: CSV -> CSV
addtotals
      | ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(Text, PeriodicReport DisplayName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = CSV -> CSV
forall a. a -> a
id
      | Bool
otherwise = (CSV -> CSV -> CSV
forall a. [a] -> [a] -> [a]
++ ([Text] -> [Text]) -> CSV -> CSV
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text
"Net:" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: ) (ReportOpts -> [DateSpan] -> PeriodicReportRow () MixedAmount -> CSV
forall a.
ReportOpts -> [DateSpan] -> PeriodicReportRow a MixedAmount -> CSV
multiBalanceRowAsCsvText ReportOpts
ropts [DateSpan]
colspans PeriodicReportRow () MixedAmount
netrow))

-- | Render a compound balance report as HTML.
compoundBalanceReportAsHtml :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> Html ()
compoundBalanceReportAsHtml :: ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> Html ()
compoundBalanceReportAsHtml ReportOpts
ropts CompoundPeriodicReport DisplayName MixedAmount
cbr =
  let
    CompoundPeriodicReport Text
title [DateSpan]
colspans [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports PeriodicReportRow () MixedAmount
netrow = CompoundPeriodicReport DisplayName MixedAmount
cbr
    colspanattr :: Attribute
colspanattr = Text -> Attribute
colspan_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Text
T.pack (CommandDoc -> Text) -> CommandDoc -> Text
forall a b. (a -> b) -> a -> b
$ Int -> CommandDoc
forall a. Show a => a -> CommandDoc
show (Int -> CommandDoc) -> Int -> CommandDoc
forall a b. (a -> b) -> a -> b
$
      Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [DateSpan] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [DateSpan]
colspans Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then Int
1 else Int
0) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if ReportOpts -> Bool
average_ ReportOpts
ropts then Int
1 else Int
0)
    leftattr :: Attribute
leftattr = Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:left"
    blankrow :: Html ()
blankrow = Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
td_ [Attribute
colspanattr] (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtmlRaw (CommandDoc
"&nbsp;"::String)

    titlerows :: [Html ()]
titlerows =
      (Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Attribute
colspanattr, Attribute
leftattr] (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ Html () -> Html ()
forall arg result. Term arg result => arg -> result
h2_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
title)
      Html () -> [Html ()] -> [Html ()]
forall a. a -> [a] -> [a]
: [[Text] -> Html ()
thRow ([Text] -> Html ()) -> [Text] -> Html ()
forall a b. (a -> b) -> a -> b
$
         Text
"" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text
"Commodity" | ReportOpts -> Layout
layout_ ReportOpts
ropts Layout -> Layout -> Bool
forall a. Eq a => a -> a -> Bool
== Layout
LayoutBare] [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 (ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts) [DateSpan]
colspans) [DateSpan]
colspans
         [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [Text
"Total"] else [])
         [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts then [Text
"Average"] else [])
        ]

    thRow :: [T.Text] -> Html ()
    thRow :: [Text] -> Html ()
thRow = Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> ([Text] -> Html ()) -> [Text] -> Html ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Html ()] -> Html ()
forall a. Monoid a => [a] -> a
mconcat ([Html ()] -> Html ())
-> ([Text] -> [Html ()]) -> [Text] -> Html ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Html ()) -> [Text] -> [Html ()]
forall a b. (a -> b) -> [a] -> [b]
map (Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ (Html () -> Html ()) -> (Text -> Html ()) -> Text -> Html ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml)

    -- Make rows for a subreport: its title row, not the headings row,
    -- the data rows, any totals row, and a blank row for whitespace.
    subreportrows :: (T.Text, MultiBalanceReport, Bool) -> [Html ()]
    subreportrows :: (Text, PeriodicReport DisplayName MixedAmount, Bool) -> [Html ()]
subreportrows (Text
subreporttitle, PeriodicReport DisplayName MixedAmount
mbr, Bool
_increasestotal) =
      let
        (Html ()
_,[Html ()]
bodyrows,[Html ()]
mtotalsrows) = ReportOpts
-> PeriodicReport DisplayName MixedAmount
-> (Html (), [Html ()], [Html ()])
multiBalanceReportHtmlRows ReportOpts
ropts PeriodicReport DisplayName MixedAmount
mbr
      in
           [Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ [Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Attribute
colspanattr, Attribute
leftattr] (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ Text -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml Text
subreporttitle]
        [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
bodyrows
        [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
mtotalsrows
        [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()
blankrow]

    totalrows :: [Html ()]
totalrows | ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(Text, PeriodicReport DisplayName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = []
      | Bool
otherwise = ReportOpts -> [Text] -> Html ()
multiBalanceReportHtmlFootRow ReportOpts
ropts ([Text] -> Html ()) -> CSV -> [Html ()]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text
"Net:" 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 -> [DateSpan] -> PeriodicReportRow () MixedAmount -> CSV
forall a.
ReportOpts -> [DateSpan] -> PeriodicReportRow a MixedAmount -> CSV
multiBalanceRowAsCsvText ReportOpts
ropts [DateSpan]
colspans PeriodicReportRow () MixedAmount
netrow)
  in do
    Text -> Html ()
forall arg result. TermRaw arg result => arg -> result
style_ ([Text] -> Text
T.unlines [Text
""
      ,Text
"td { padding:0 0.5em; }"
      ,Text
"td:nth-child(1) { white-space:nowrap; }"
      ,Text
"tr:nth-child(even) td { background-color:#eee; }"
      ])
    [Attribute] -> Html ()
forall (m :: * -> *). Applicative m => [Attribute] -> HtmlT m ()
link_ [Text -> Attribute
rel_ Text
"stylesheet", Text -> Attribute
href_ Text
"hledger.css"]
    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 ()]
titlerows
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()
blankrow]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ ((Text, PeriodicReport DisplayName MixedAmount, Bool) -> [Html ()])
-> [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
-> [Html ()]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Text, PeriodicReport DisplayName MixedAmount, Bool) -> [Html ()]
subreportrows [(Text, PeriodicReport DisplayName MixedAmount, Bool)]
subreports
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
totalrows