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

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
import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL
import Data.Time.Calendar
import System.Console.CmdArgs.Explicit as C
import Hledger.Read.CsvReader (CSV, printCSV)
import Lucid as L hiding (value_)
import Text.Tabular as T

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

-- | 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 -> BalanceType
cbctype     :: BalanceType                      -- ^ the "balance" type (change, cumulative, historical)
                                                  --   this report shows (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]
BalanceType
cbctype :: BalanceType
cbcqueries :: [CBCSubreportSpec DisplayName]
cbctitle :: CommandDoc
cbcdoc :: CommandDoc
cbctype :: CompoundBalanceCommandSpec -> BalanceType
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
"change"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"change")
       (CommandDoc
"show balance change in each period" CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ BalanceType -> CommandDoc
defType BalanceType
PeriodChange)
    ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"cumulative"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"cumulative")
       (CommandDoc
"show balance change accumulated across periods (in multicolumn reports)"
           CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ BalanceType -> CommandDoc
defType BalanceType
CumulativeChange
       )
    ,[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
"show historical ending balance in each period (includes postings before report start date)"
           CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ BalanceType -> CommandDoc
defType BalanceType
HistoricalBalance
       )
    ]
    [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
"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
"pretty-tables"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"pretty-tables") CommandDoc
"use unicode when displaying tables"
    ,[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] -> 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]")
 where
   defType :: BalanceType -> String
   defType :: BalanceType -> CommandDoc
defType BalanceType
bt | BalanceType
bt BalanceType -> BalanceType -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceType
cbctype = 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]
BalanceType
cbctype :: BalanceType
cbcqueries :: [CBCSubreportSpec DisplayName]
cbctitle :: CommandDoc
cbcdoc :: CommandDoc
cbctype :: CompoundBalanceCommandSpec -> BalanceType
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
    let
      ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe ValuationType
Maybe DateSpan
Maybe NormalSign
BalanceType
AccountListMode
StringFormat
Period
Interval
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
value_ :: ReportOpts -> Maybe ValuationType
infer_value_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
querystring_ :: ReportOpts -> [Text]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
txn_dates_ :: ReportOpts -> Bool
balancetype_ :: ReportOpts -> BalanceType
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
pretty_tables_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
forecast_ :: ReportOpts -> Maybe DateSpan
transpose_ :: ReportOpts -> Bool
transpose_ :: Bool
forecast_ :: Maybe DateSpan
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
pretty_tables_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
balancetype_ :: BalanceType
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_value_ :: Bool
value_ :: Maybe ValuationType
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
..} = ReportSpec -> ReportOpts
rsOpts ReportSpec
rspec
      -- use the default balance type for this report, unless the user overrides
      mBalanceTypeOverride :: Maybe BalanceType
mBalanceTypeOverride =
        (CommandDoc -> Maybe BalanceType) -> RawOpts -> Maybe BalanceType
forall a. (CommandDoc -> Maybe a) -> RawOpts -> Maybe a
choiceopt CommandDoc -> Maybe BalanceType
parse RawOpts
rawopts where
          parse :: CommandDoc -> Maybe BalanceType
parse = \case
            CommandDoc
"historical" -> BalanceType -> Maybe BalanceType
forall a. a -> Maybe a
Just BalanceType
HistoricalBalance
            CommandDoc
"cumulative" -> BalanceType -> Maybe BalanceType
forall a. a -> Maybe a
Just BalanceType
CumulativeChange
            CommandDoc
"change"     -> BalanceType -> Maybe BalanceType
forall a. a -> Maybe a
Just BalanceType
PeriodChange
            CommandDoc
_            -> Maybe BalanceType
forall a. Maybe a
Nothing
      balancetype :: BalanceType
balancetype = BalanceType -> Maybe BalanceType -> BalanceType
forall a. a -> Maybe a -> a
fromMaybe BalanceType
cbctype Maybe BalanceType
mBalanceTypeOverride
      -- Set balance type in the report options.
      ropts' :: ReportOpts
ropts' = ReportOpts
ropts{balancetype_ :: BalanceType
balancetype_=BalanceType
balancetype}

      title :: CommandDoc
title =
        CommandDoc
cbctitle
        CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
" "
        CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
titledatestr
        CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
-> (CommandDoc -> CommandDoc) -> Maybe CommandDoc -> CommandDoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe CommandDoc
"" (Char
' 'Char -> CommandDoc -> CommandDoc
forall a. a -> [a] -> [a]
:) Maybe CommandDoc
mtitleclarification
        CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
valuationdesc
        where

          -- XXX #1078 the title of ending balance reports
          -- (HistoricalBalance) 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 :: CommandDoc
titledatestr = case BalanceType
balancetype of
              BalanceType
HistoricalBalance -> [Day] -> CommandDoc
showEndDates [Day]
enddates
              BalanceType
_                 -> DateSpan -> CommandDoc
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 = Bool -> Query -> DateSpan
queryDateSpan Bool
date2_ (ReportSpec -> Query
rsQuery ReportSpec
rspec)
                                  DateSpan -> DateSpan -> DateSpan
`spanDefaultsFrom` Bool -> Journal -> DateSpan
journalDateSpan Bool
date2_ Journal
j

          -- when user overrides, add an indication to the report title
          mtitleclarification :: Maybe CommandDoc
mtitleclarification = ((BalanceType -> CommandDoc)
 -> Maybe BalanceType -> Maybe CommandDoc)
-> Maybe BalanceType
-> (BalanceType -> CommandDoc)
-> Maybe CommandDoc
forall a b c. (a -> b -> c) -> b -> a -> c
flip (BalanceType -> CommandDoc)
-> Maybe BalanceType -> Maybe CommandDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe BalanceType
mBalanceTypeOverride ((BalanceType -> CommandDoc) -> Maybe CommandDoc)
-> (BalanceType -> CommandDoc) -> Maybe CommandDoc
forall a b. (a -> b) -> a -> b
$ \case
              BalanceType
PeriodChange                     -> CommandDoc
"(Balance Changes)"
              BalanceType
CumulativeChange                 -> CommandDoc
"(Cumulative Ending Balances)"
              BalanceType
HistoricalBalance                -> CommandDoc
"(Historical Ending Balances)"

          valuationdesc :: CommandDoc
valuationdesc = case Maybe ValuationType
value_ of
            Just (AtCost Maybe Text
_mc)       -> CommandDoc
", valued at cost"
            Just (AtThen Maybe Text
_mc)       -> CommandDoc -> CommandDoc
forall a. CommandDoc -> a
error' CommandDoc
unsupportedValueThenError  -- TODO
            Just (AtEnd Maybe Text
_mc)        -> CommandDoc
", valued at period ends"
            Just (AtNow Maybe Text
_mc)        -> CommandDoc
", current value"
            Just (AtDefault Maybe Text
_mc) | Bool
multiperiod       -> CommandDoc
", valued at period ends"
            Just (AtDefault Maybe Text
_mc)    -> CommandDoc
", current value"
            Just (AtDate Day
today Maybe Text
_mc) -> CommandDoc
", valued at "CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++Day -> CommandDoc
showDate Day
today
            Maybe ValuationType
Nothing                 -> CommandDoc
""

          multiperiod :: Bool
multiperiod = Interval
interval_ Interval -> Interval -> Bool
forall a. Eq a => a -> a -> Bool
/= Interval
NoInterval

      -- 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{rsOpts :: ReportOpts
rsOpts=ReportOpts
ropts'} Journal
j [CBCSubreportSpec DisplayName]
cbcqueries
      cbr :: CompoundPeriodicReport DisplayName MixedAmount
cbr  = CompoundPeriodicReport DisplayName MixedAmount
cbr'{cbrTitle :: CommandDoc
cbrTitle=CommandDoc
title}

    -- render appropriately
    CliOpts -> CommandDoc -> IO ()
writeOutput CliOpts
opts (CommandDoc -> IO ()) -> CommandDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ case CliOpts -> CommandDoc
outputFormatFromOpts CliOpts
opts of
        CommandDoc
"txt"  -> ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> CommandDoc
compoundBalanceReportAsText ReportOpts
ropts' CompoundPeriodicReport DisplayName MixedAmount
cbr
        CommandDoc
"csv"  -> CSV -> CommandDoc
printCSV (ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV
compoundBalanceReportAsCsv ReportOpts
ropts CompoundPeriodicReport DisplayName MixedAmount
cbr) CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
"\n"
        CommandDoc
"html" -> (CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++CommandDoc
"\n") (CommandDoc -> CommandDoc) -> CommandDoc -> CommandDoc
forall a b. (a -> b) -> a -> b
$ Text -> CommandDoc
TL.unpack (Text -> CommandDoc) -> Text -> CommandDoc
forall a b. (a -> b) -> a -> b
$ Html () -> Text
forall a. Html a -> Text
L.renderText (Html () -> Text) -> Html () -> Text
forall a b. (a -> b) -> a -> b
$ ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> Html ()
compoundBalanceReportAsHtml ReportOpts
ropts CompoundPeriodicReport DisplayName MixedAmount
cbr
        CommandDoc
"json" -> (CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++CommandDoc
"\n") (CommandDoc -> CommandDoc) -> CommandDoc -> CommandDoc
forall a b. (a -> b) -> a -> b
$ Text -> CommandDoc
TL.unpack (Text -> CommandDoc) -> Text -> CommandDoc
forall a b. (a -> b) -> a -> b
$ CompoundPeriodicReport DisplayName MixedAmount -> Text
forall a. ToJSON a => a -> Text
toJsonText CompoundPeriodicReport DisplayName MixedAmount
cbr
        CommandDoc
x      -> CommandDoc -> CommandDoc
forall a. CommandDoc -> a
error' (CommandDoc -> CommandDoc) -> CommandDoc -> CommandDoc
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] -> String
showEndDates :: [Day] -> CommandDoc
showEndDates [Day]
es = case [Day]
es of
  -- cf showPeriod
  (Day
e:Day
_:[Day]
_) -> Day -> CommandDoc
showdate Day
e CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
".." CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ Day -> CommandDoc
showdate ([Day] -> Day
forall a. [a] -> a
last [Day]
es)
  [Day
e]     -> Day -> CommandDoc
showdate Day
e
  []      -> CommandDoc
""
  where
    showdate :: Day -> CommandDoc
showdate = Day -> CommandDoc
forall a. Show a => a -> CommandDoc
show

-- | 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 -> String
compoundBalanceReportAsText :: ReportOpts
-> CompoundPeriodicReport DisplayName MixedAmount -> CommandDoc
compoundBalanceReportAsText ReportOpts
ropts
  (CompoundPeriodicReport CommandDoc
title [DateSpan]
_colspans [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports (PeriodicReportRow ()
_ [MixedAmount]
coltotals MixedAmount
grandtotal MixedAmount
grandavg)) =
    CommandDoc
title CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
"\n\n" CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++
    ReportOpts -> Table CommandDoc CommandDoc MixedAmount -> CommandDoc
balanceReportTableAsText ReportOpts
ropts Table CommandDoc CommandDoc MixedAmount
bigtable'
  where
    bigtable :: Table CommandDoc CommandDoc MixedAmount
bigtable =
      case ((CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
 -> Table CommandDoc CommandDoc MixedAmount)
-> [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
-> [Table CommandDoc CommandDoc MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map (ReportOpts
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
-> Table CommandDoc CommandDoc MixedAmount
forall c.
ReportOpts
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, c)
-> Table CommandDoc CommandDoc MixedAmount
subreportAsTable ReportOpts
ropts) [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports of
        []   -> Table CommandDoc CommandDoc MixedAmount
forall rh ch a. Table rh ch a
T.empty
        Table CommandDoc CommandDoc MixedAmount
r:[Table CommandDoc CommandDoc MixedAmount]
rs -> (Table CommandDoc CommandDoc MixedAmount
 -> Table CommandDoc CommandDoc MixedAmount
 -> Table CommandDoc CommandDoc MixedAmount)
-> Table CommandDoc CommandDoc MixedAmount
-> [Table CommandDoc CommandDoc MixedAmount]
-> Table CommandDoc CommandDoc MixedAmount
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Table CommandDoc CommandDoc MixedAmount
-> Table CommandDoc CommandDoc MixedAmount
-> Table CommandDoc CommandDoc MixedAmount
forall rh ch a ch. Table rh ch a -> Table rh ch a -> Table rh ch a
concatTables Table CommandDoc CommandDoc MixedAmount
r [Table CommandDoc CommandDoc MixedAmount]
rs
    bigtable' :: Table CommandDoc CommandDoc MixedAmount
bigtable'
      | ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 =
          Table CommandDoc CommandDoc MixedAmount
bigtable
      | Bool
otherwise =
          Table CommandDoc CommandDoc MixedAmount
bigtable
          Table CommandDoc CommandDoc MixedAmount
-> SemiTable CommandDoc MixedAmount
-> Table CommandDoc CommandDoc MixedAmount
forall rh ch a. Table rh ch a -> SemiTable rh a -> Table rh ch a
+====+
          CommandDoc -> [MixedAmount] -> SemiTable CommandDoc MixedAmount
forall rh a. rh -> [a] -> SemiTable rh a
row CommandDoc
"Net:" (
            [MixedAmount]
coltotals
            [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [MixedAmount
grandtotal] else [])
            [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts   then [MixedAmount
grandavg]   else [])
            )

    -- | Convert a named multi balance report to a table suitable for
    -- concatenating with others to make a compound balance report table.
    subreportAsTable :: ReportOpts
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, c)
-> Table CommandDoc CommandDoc MixedAmount
subreportAsTable ReportOpts
ropts (CommandDoc
title, PeriodicReport DisplayName MixedAmount
r, c
_) = Table CommandDoc CommandDoc MixedAmount
t
      where
        -- convert to table
        Table Header CommandDoc
lefthdrs Header CommandDoc
tophdrs [[MixedAmount]]
cells = ReportOpts
-> PeriodicReport DisplayName MixedAmount
-> Table CommandDoc CommandDoc MixedAmount
balanceReportAsTable ReportOpts
ropts PeriodicReport DisplayName MixedAmount
r
        -- tweak the layout
        t :: Table CommandDoc CommandDoc MixedAmount
t = Header CommandDoc
-> Header CommandDoc
-> [[MixedAmount]]
-> Table CommandDoc CommandDoc MixedAmount
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table (Properties -> [Header CommandDoc] -> Header CommandDoc
forall h. Properties -> [Header h] -> Header h
T.Group Properties
SingleLine [CommandDoc -> Header CommandDoc
forall h. h -> Header h
Header CommandDoc
title, Header CommandDoc
lefthdrs]) Header CommandDoc
tophdrs ([][MixedAmount] -> [[MixedAmount]] -> [[MixedAmount]]
forall a. a -> [a] -> [a]
:[[MixedAmount]]
cells)

-- | Add the second table below the first, discarding its column headings.
concatTables :: Table rh ch a -> Table rh ch a -> Table rh ch a
concatTables (Table Header rh
hLeft Header ch
hTop [[a]]
dat) (Table Header rh
hLeft' Header ch
_ [[a]]
dat') =
    Header rh -> Header ch -> [[a]] -> Table rh ch a
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table (Properties -> [Header rh] -> Header rh
forall h. Properties -> [Header h] -> Header h
T.Group Properties
DoubleLine [Header rh
hLeft, Header rh
hLeft']) Header ch
hTop ([[a]]
dat [[a]] -> [[a]] -> [[a]]
forall a. [a] -> [a] -> [a]
++ [[a]]
dat')

-- | 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 CommandDoc
title [DateSpan]
colspans [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports (PeriodicReportRow ()
_ [MixedAmount]
coltotals MixedAmount
grandtotal MixedAmount
grandavg)) =
  CSV -> CSV
addtotals (CSV -> CSV) -> CSV -> CSV
forall a b. (a -> b) -> a -> b
$
  CommandDoc -> [CommandDoc]
forall a. IsString a => a -> [a]
padRow CommandDoc
title [CommandDoc] -> CSV -> CSV
forall a. a -> [a] -> [a]
:
  (CommandDoc
"Account" CommandDoc -> [CommandDoc] -> [CommandDoc]
forall a. a -> [a] -> [a]
:
   (DateSpan -> CommandDoc) -> [DateSpan] -> [CommandDoc]
forall a b. (a -> b) -> [a] -> [b]
map DateSpan -> CommandDoc
showDateSpanMonthAbbrev [DateSpan]
colspans
   [CommandDoc] -> [CommandDoc] -> [CommandDoc]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [CommandDoc
"Total"] else [])
   [CommandDoc] -> [CommandDoc] -> [CommandDoc]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts then [CommandDoc
"Average"] else [])
   ) [CommandDoc] -> CSV -> CSV
forall a. a -> [a] -> [a]
:
  ((CommandDoc, PeriodicReport DisplayName MixedAmount, Bool) -> CSV)
-> [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
-> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ReportOpts
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
-> CSV
forall c.
ReportOpts
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, c) -> CSV
subreportAsCsv ReportOpts
ropts) [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports
  where
    -- | Add a subreport title row and drop the heading row.
    subreportAsCsv :: ReportOpts
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, c) -> CSV
subreportAsCsv ReportOpts
ropts (CommandDoc
subreporttitle, PeriodicReport DisplayName MixedAmount
multibalreport, c
_) =
      CommandDoc -> [CommandDoc]
forall a. IsString a => a -> [a]
padRow CommandDoc
subreporttitle [CommandDoc] -> 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
          | [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(CommandDoc, 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 -> 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
            ((CommandDoc, PeriodicReport DisplayName MixedAmount, Bool) -> Int)
-> [(CommandDoc, 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)
-> ((CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
    -> [DateSpan])
-> (CommandDoc, 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])
-> ((CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
    -> PeriodicReport DisplayName MixedAmount)
-> (CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
-> [DateSpan]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
-> PeriodicReport DisplayName MixedAmount
forall a b c. (a, b, c) -> b
second3) [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports
    addtotals :: CSV -> CSV
addtotals
      | ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, 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]
++
          [CommandDoc
"Net:" CommandDoc -> [CommandDoc] -> [CommandDoc]
forall a. a -> [a] -> [a]
:
           (MixedAmount -> CommandDoc) -> [MixedAmount] -> [CommandDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice Bool
False) (
             [MixedAmount]
coltotals
             [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [MixedAmount
grandtotal] else [])
             [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts   then [MixedAmount
grandavg]   else [])
             )
          ])

-- | 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 CommandDoc
title [DateSpan]
colspans [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports (PeriodicReportRow ()
_ [MixedAmount]
coltotals MixedAmount
grandtotal MixedAmount
grandavg) = CompoundPeriodicReport DisplayName MixedAmount
cbr
    colspanattr :: Attribute
colspanattr = Text -> Attribute
colspan_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Text
TS.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
" "::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
$ CommandDoc -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml CommandDoc
title]
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [[CommandDoc] -> Html ()
thRow ([CommandDoc] -> Html ()) -> [CommandDoc] -> Html ()
forall a b. (a -> b) -> a -> b
$
          CommandDoc
"" CommandDoc -> [CommandDoc] -> [CommandDoc]
forall a. a -> [a] -> [a]
:
          (DateSpan -> CommandDoc) -> [DateSpan] -> [CommandDoc]
forall a b. (a -> b) -> [a] -> [b]
map DateSpan -> CommandDoc
showDateSpanMonthAbbrev [DateSpan]
colspans
          [CommandDoc] -> [CommandDoc] -> [CommandDoc]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [CommandDoc
"Total"] else [])
          [CommandDoc] -> [CommandDoc] -> [CommandDoc]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts then [CommandDoc
"Average"] else [])
          ]

    thRow :: [String] -> Html ()
    thRow :: [CommandDoc] -> Html ()
thRow = Html () -> Html ()
forall arg result. Term arg result => arg -> result
tr_ (Html () -> Html ())
-> ([CommandDoc] -> Html ()) -> [CommandDoc] -> Html ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Html ()] -> Html ()
forall a. Monoid a => [a] -> a
mconcat ([Html ()] -> Html ())
-> ([CommandDoc] -> [Html ()]) -> [CommandDoc] -> Html ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommandDoc -> Html ()) -> [CommandDoc] -> [Html ()]
forall a b. (a -> b) -> [a] -> [b]
map (Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ (Html () -> Html ())
-> (CommandDoc -> Html ()) -> CommandDoc -> Html ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandDoc -> 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 :: (String, MultiBalanceReport, Bool) -> [Html ()]
    subreportrows :: (CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
-> [Html ()]
subreportrows (CommandDoc
subreporttitle, PeriodicReport DisplayName MixedAmount
mbr, Bool
_increasestotal) =
      let
        (Html ()
_,[Html ()]
bodyrows,Maybe (Html ())
mtotalsrow) = ReportOpts
-> PeriodicReport DisplayName MixedAmount
-> (Html (), [Html ()], Maybe (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
$ CommandDoc -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml CommandDoc
subreporttitle]
        [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
bodyrows
        [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()] -> (Html () -> [Html ()]) -> Maybe (Html ()) -> [Html ()]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Html () -> [Html ()] -> [Html ()]
forall a. a -> [a] -> [a]
:[]) Maybe (Html ())
mtotalsrow
        [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()
blankrow]

    totalrows :: [Html ()]
totalrows | ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = []
              | Bool
otherwise =
                  let defstyle :: Attribute
defstyle = Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:right"
                  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
class_ Text
"", Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"text-align:left"] Html ()
"Net:"
                       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] (CommandDoc -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml (CommandDoc -> Html ()) -> CommandDoc -> Html ()
forall a b. (a -> b) -> a -> b
$ Bool -> MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice Bool
False MixedAmount
a) | MixedAmount
a <- [MixedAmount]
coltotals]
                      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
row_total_ ReportOpts
ropts then [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Text -> Attribute
class_ Text
"amount coltotal", Attribute
defstyle] (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml (CommandDoc -> Html ()) -> CommandDoc -> Html ()
forall a b. (a -> b) -> a -> b
$ Bool -> MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice Bool
False MixedAmount
grandtotal] else [])
                      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ (if ReportOpts -> Bool
average_ ReportOpts
ropts   then [[Attribute] -> Html () -> Html ()
forall arg result. Term arg result => arg -> result
th_ [Text -> Attribute
class_ Text
"amount colaverage", Attribute
defstyle] (Html () -> Html ()) -> Html () -> Html ()
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Html ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtml (CommandDoc -> Html ()) -> CommandDoc -> Html ()
forall a b. (a -> b) -> a -> b
$ Bool -> MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice Bool
False MixedAmount
grandavg] else [])
                    ]

  in do
    Text -> Html ()
forall arg result. TermRaw arg result => arg -> result
style_ ([Text] -> Text
TS.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]
++ ((CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
 -> [Html ()])
-> [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
-> [Html ()]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)
-> [Html ()]
subreportrows [(CommandDoc, PeriodicReport DisplayName MixedAmount, Bool)]
subreports
      [Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
totalrows