{-# LANGUAGE OverloadedStrings, RecordWildCards, LambdaCase #-}
module Hledger.Cli.CompoundBalanceCommand (
CompoundBalanceCommandSpec(..)
,CBCSubreportSpec(..)
,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)
data CompoundBalanceCommandSpec = CompoundBalanceCommandSpec {
CompoundBalanceCommandSpec -> CommandDoc
cbcdoc :: CommandDoc,
CompoundBalanceCommandSpec -> CommandDoc
cbctitle :: String,
CompoundBalanceCommandSpec -> [CBCSubreportSpec]
cbcqueries :: [CBCSubreportSpec],
CompoundBalanceCommandSpec -> BalanceType
cbctype :: BalanceType
}
data CBCSubreportSpec = CBCSubreportSpec {
CBCSubreportSpec -> CommandDoc
cbcsubreporttitle :: String
,CBCSubreportSpec -> Journal -> Query
cbcsubreportquery :: Journal -> Query
,CBCSubreportSpec -> NormalSign
cbcsubreportnormalsign :: NormalSign
,CBCSubreportSpec -> Bool
cbcsubreportincreasestotal :: Bool
}
type CompoundBalanceReport =
( String
, [DateSpan]
, [(String, MultiBalanceReport, Bool)]
, ([MixedAmount], MixedAmount, MixedAmount)
)
compoundBalanceCommandMode :: CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode :: CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode CompoundBalanceCommandSpec{CommandDoc
[CBCSubreportSpec]
BalanceType
cbctype :: BalanceType
cbcqueries :: [CBCSubreportSpec]
cbctitle :: CommandDoc
cbcdoc :: CommandDoc
cbctype :: CompoundBalanceCommandSpec -> BalanceType
cbcqueries :: CompoundBalanceCommandSpec -> [CBCSubreportSpec]
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
)
,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"flat"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"flat") CommandDoc
"show accounts as a list"
,[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
"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
"tree"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"tree") CommandDoc
"show accounts as a tree; amounts include subaccounts (default in simple reports)"
,[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-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
"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
""
compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> IO ())
compoundBalanceCommand :: CompoundBalanceCommandSpec -> CliOpts -> Journal -> IO ()
compoundBalanceCommand CompoundBalanceCommandSpec{CommandDoc
[CBCSubreportSpec]
BalanceType
cbctype :: BalanceType
cbcqueries :: [CBCSubreportSpec]
cbctitle :: CommandDoc
cbcdoc :: CommandDoc
cbctype :: CompoundBalanceCommandSpec -> BalanceType
cbcqueries :: CompoundBalanceCommandSpec -> [CBCSubreportSpec]
cbctitle :: CompoundBalanceCommandSpec -> CommandDoc
cbcdoc :: CompoundBalanceCommandSpec -> CommandDoc
..} opts :: CliOpts
opts@CliOpts{reportopts_ :: CliOpts -> ReportOpts
reportopts_=ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
CommandDoc
[Status]
Maybe Int
Maybe CommandDoc
Maybe ValuationType
Maybe DateSpan
Maybe NormalSign
Maybe Day
BalanceType
AccountListMode
Period
Interval
today_ :: ReportOpts -> Maybe Day
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
value_ :: ReportOpts -> Maybe ValuationType
infer_value_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
display_ :: ReportOpts -> Maybe CommandDoc
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> Maybe CommandDoc
query_ :: ReportOpts -> CommandDoc
average_ :: ReportOpts -> Bool
related_ :: 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
related_ :: Bool
average_ :: Bool
query_ :: CommandDoc
format_ :: Maybe CommandDoc
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
display_ :: Maybe CommandDoc
depth_ :: Maybe Int
infer_value_ :: Bool
value_ :: Maybe ValuationType
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
today_ :: Maybe Day
..}, rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts} Journal
j = do
Day
d <- IO Day
getCurrentDay
let
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
ropts' :: ReportOpts
ropts' = ReportOpts
ropts{
balancetype_ :: BalanceType
balancetype_=BalanceType
balancetype,
accountlistmode_ :: AccountListMode
accountlistmode_=if Bool -> Bool
not (ReportOpts -> Bool
flat_ ReportOpts
ropts) Bool -> Bool -> Bool
&& Interval
interval_Interval -> Interval -> Bool
forall a. Eq a => a -> a -> Bool
==Interval
NoInterval Bool -> Bool -> Bool
&& BalanceType
balancetype BalanceType -> [BalanceType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [BalanceType
CumulativeChange, BalanceType
HistoricalBalance] then AccountListMode
ALTree else AccountListMode
accountlistmode_,
no_total_ :: Bool
no_total_=if Bool
percent_ Bool -> Bool -> Bool
&& [CBCSubreportSpec] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CBCSubreportSpec]
cbcqueries Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then Bool
True else Bool
no_total_
}
userq :: Query
userq = Day -> ReportOpts -> Query
queryFromOpts Day
d ReportOpts
ropts'
fmt :: CommandDoc
fmt = CliOpts -> CommandDoc
outputFormatFromOpts CliOpts
opts
priceoracle :: PriceOracle
priceoracle = Bool -> Journal -> PriceOracle
journalPriceOracle Bool
infer_value_ Journal
j
subreports :: [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports =
(CBCSubreportSpec
-> (CommandDoc, PeriodicReport AccountName MixedAmount, Bool))
-> [CBCSubreportSpec]
-> [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
forall a b. (a -> b) -> [a] -> [b]
map (\CBCSubreportSpec{Bool
CommandDoc
NormalSign
Journal -> Query
cbcsubreportincreasestotal :: Bool
cbcsubreportnormalsign :: NormalSign
cbcsubreportquery :: Journal -> Query
cbcsubreporttitle :: CommandDoc
cbcsubreportincreasestotal :: CBCSubreportSpec -> Bool
cbcsubreportnormalsign :: CBCSubreportSpec -> NormalSign
cbcsubreportquery :: CBCSubreportSpec -> Journal -> Query
cbcsubreporttitle :: CBCSubreportSpec -> CommandDoc
..} ->
(CommandDoc
cbcsubreporttitle
,NormalSign
-> PeriodicReport AccountName MixedAmount
-> PeriodicReport AccountName MixedAmount
forall b a.
Num b =>
NormalSign -> PeriodicReport a b -> PeriodicReport a b
prNormaliseSign NormalSign
cbcsubreportnormalsign (PeriodicReport AccountName MixedAmount
-> PeriodicReport AccountName MixedAmount)
-> PeriodicReport AccountName MixedAmount
-> PeriodicReport AccountName MixedAmount
forall a b. (a -> b) -> a -> b
$
ReportOpts
-> Query
-> Journal
-> PriceOracle
-> (Journal -> Query)
-> NormalSign
-> PeriodicReport AccountName MixedAmount
compoundBalanceSubreport ReportOpts
ropts' Query
userq Journal
j PriceOracle
priceoracle Journal -> Query
cbcsubreportquery NormalSign
cbcsubreportnormalsign
,Bool
cbcsubreportincreasestotal
))
[CBCSubreportSpec]
cbcqueries
subtotalrows :: [([MixedAmount], Bool)]
subtotalrows =
[(PeriodicReportRow () MixedAmount -> [MixedAmount]
forall a b. PeriodicReportRow a b -> [b]
prrAmounts (PeriodicReportRow () MixedAmount -> [MixedAmount])
-> PeriodicReportRow () MixedAmount -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$ PeriodicReport AccountName MixedAmount
-> PeriodicReportRow () MixedAmount
forall a b. PeriodicReport a b -> PeriodicReportRow () b
prTotals PeriodicReport AccountName MixedAmount
report, Bool
increasesoveralltotal)
| (CommandDoc
_, PeriodicReport AccountName MixedAmount
report, Bool
increasesoveralltotal) <- [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports
]
overalltotals :: ([MixedAmount], MixedAmount, MixedAmount)
overalltotals = case [([MixedAmount], Bool)]
subtotalrows of
[] -> ([], MixedAmount
nullmixedamt, MixedAmount
nullmixedamt)
[([MixedAmount], Bool)]
rs ->
let
numcols :: Int
numcols = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (([MixedAmount], Bool) -> Int) -> [([MixedAmount], Bool)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([MixedAmount] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length([MixedAmount] -> Int)
-> (([MixedAmount], Bool) -> [MixedAmount])
-> ([MixedAmount], Bool)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([MixedAmount], Bool) -> [MixedAmount]
forall a b. (a, b) -> a
fst) [([MixedAmount], Bool)]
rs
paddedsignedsubtotalrows :: [[MixedAmount]]
paddedsignedsubtotalrows =
[(MixedAmount -> MixedAmount) -> [MixedAmount] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map (if Bool
increasesoveralltotal then MixedAmount -> MixedAmount
forall a. a -> a
id else MixedAmount -> MixedAmount
forall a. Num a => a -> a
negate) ([MixedAmount] -> [MixedAmount]) -> [MixedAmount] -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$
Int -> [MixedAmount] -> [MixedAmount]
forall a. Int -> [a] -> [a]
take Int
numcols ([MixedAmount] -> [MixedAmount]) -> [MixedAmount] -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$ [MixedAmount]
as [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a. [a] -> [a] -> [a]
++ MixedAmount -> [MixedAmount]
forall a. a -> [a]
repeat MixedAmount
nullmixedamt
| ([MixedAmount]
as,Bool
increasesoveralltotal) <- [([MixedAmount], Bool)]
rs
]
coltotals :: [MixedAmount]
coltotals = ([MixedAmount] -> [MixedAmount] -> [MixedAmount])
-> [MixedAmount] -> [[MixedAmount]] -> [MixedAmount]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((MixedAmount -> MixedAmount -> MixedAmount)
-> [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith MixedAmount -> MixedAmount -> MixedAmount
forall a. Num a => a -> a -> a
(+)) [MixedAmount]
zeros [[MixedAmount]]
paddedsignedsubtotalrows
where zeros :: [MixedAmount]
zeros = Int -> MixedAmount -> [MixedAmount]
forall a. Int -> a -> [a]
replicate Int
numcols MixedAmount
nullmixedamt
grandtotal :: MixedAmount
grandtotal = [MixedAmount] -> MixedAmount
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [MixedAmount]
coltotals
grandavg :: MixedAmount
grandavg | [MixedAmount] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MixedAmount]
coltotals = MixedAmount
nullmixedamt
| Bool
otherwise = Int -> Quantity
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([MixedAmount] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [MixedAmount]
coltotals) Quantity -> MixedAmount -> MixedAmount
`divideMixedAmount` MixedAmount
grandtotal
in
([MixedAmount]
coltotals, MixedAmount
grandtotal, MixedAmount
grandavg)
colspans :: [DateSpan]
colspans =
case [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports of
(CommandDoc
_, PeriodicReport [DateSpan]
ds [PeriodicReportRow AccountName MixedAmount]
_ PeriodicReportRow () MixedAmount
_, Bool
_):[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
_ -> [DateSpan]
ds
[] -> []
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
titledatestr :: CommandDoc
titledatestr
| BalanceType
balancetype BalanceType -> BalanceType -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceType
HistoricalBalance = [Day] -> CommandDoc
showEndDates [Day]
enddates
| Bool
otherwise = 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]) -> [Day] -> [Day]
forall a b. (a -> b) -> a -> b
$ [Maybe Day] -> [Day]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Day] -> [Day]) -> [Maybe Day] -> [Day]
forall a b. (a -> b) -> a -> b
$ (DateSpan -> Maybe Day) -> [DateSpan] -> [Maybe Day]
forall a b. (a -> b) -> [a] -> [b]
map DateSpan -> Maybe Day
spanEnd [DateSpan]
colspans
requestedspan :: DateSpan
requestedspan = Bool -> Query -> DateSpan
queryDateSpan Bool
date2_ Query
userq DateSpan -> DateSpan -> DateSpan
`spanDefaultsFrom` Bool -> Journal -> DateSpan
journalDateSpan Bool
date2_ Journal
j
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
$ \BalanceType
t ->
case BalanceType
t of
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 AccountName
_mc) -> CommandDoc
", valued at cost"
Just (AtThen Maybe AccountName
_mc) -> CommandDoc -> CommandDoc
forall a. CommandDoc -> a
error' CommandDoc
unsupportedValueThenError
Just (AtEnd Maybe AccountName
_mc) -> CommandDoc
", valued at period ends"
Just (AtNow Maybe AccountName
_mc) -> CommandDoc
", current value"
Just (AtDefault Maybe AccountName
_mc) | Bool
multiperiod -> CommandDoc
", valued at period ends"
Just (AtDefault Maybe AccountName
_mc) -> CommandDoc
", current value"
Just (AtDate Day
d Maybe AccountName
_mc) -> CommandDoc
", valued at "CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++Day -> CommandDoc
showDate Day
d
Maybe ValuationType
Nothing -> CommandDoc
""
where
multiperiod :: Bool
multiperiod = Interval
interval_ Interval -> Interval -> Bool
forall a. Eq a => a -> a -> Bool
/= Interval
NoInterval
cbr :: (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
cbr =
(CommandDoc
title
,[DateSpan]
colspans
,[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports
,([MixedAmount], MixedAmount, MixedAmount)
overalltotals
)
CliOpts -> CommandDoc -> IO ()
writeOutput CliOpts
opts (CommandDoc -> IO ()) -> CommandDoc -> IO ()
forall a b. (a -> b) -> a -> b
$
case CommandDoc
fmt of
CommandDoc
"txt" -> ReportOpts
-> (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> CommandDoc
compoundBalanceReportAsText ReportOpts
ropts' (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
cbr
CommandDoc
"csv" -> CSV -> CommandDoc
printCSV (ReportOpts
-> (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> CSV
compoundBalanceReportAsCsv ReportOpts
ropts (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, 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
-> (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> Html ()
compoundBalanceReportAsHtml ReportOpts
ropts (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, 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
$ (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> Text
forall a. ToJSON a => a -> Text
toJsonText (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
cbr
CommandDoc
_ -> CommandDoc -> CommandDoc
forall a. CommandDoc -> a
error' (CommandDoc -> CommandDoc) -> CommandDoc -> CommandDoc
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
unsupportedOutputFormatError CommandDoc
fmt
showEndDates :: [Day] -> String
showEndDates :: [Day] -> CommandDoc
showEndDates [Day]
es = case [Day]
es of
(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
compoundBalanceSubreport :: ReportOpts -> Query -> Journal -> PriceOracle -> (Journal -> Query) -> NormalSign -> MultiBalanceReport
compoundBalanceSubreport :: ReportOpts
-> Query
-> Journal
-> PriceOracle
-> (Journal -> Query)
-> NormalSign
-> PeriodicReport AccountName MixedAmount
compoundBalanceSubreport ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
CommandDoc
[Status]
Maybe Int
Maybe CommandDoc
Maybe ValuationType
Maybe DateSpan
Maybe NormalSign
Maybe Day
BalanceType
AccountListMode
Period
Interval
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
related_ :: Bool
average_ :: Bool
query_ :: CommandDoc
format_ :: Maybe CommandDoc
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
display_ :: Maybe CommandDoc
depth_ :: Maybe Int
infer_value_ :: Bool
value_ :: Maybe ValuationType
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
today_ :: Maybe Day
today_ :: ReportOpts -> Maybe Day
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
value_ :: ReportOpts -> Maybe ValuationType
infer_value_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
display_ :: ReportOpts -> Maybe CommandDoc
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> Maybe CommandDoc
query_ :: ReportOpts -> CommandDoc
average_ :: ReportOpts -> Bool
related_ :: 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
..} Query
userq Journal
j PriceOracle
priceoracle Journal -> Query
subreportqfn NormalSign
subreportnormalsign = PeriodicReport AccountName MixedAmount
r'
where
ropts' :: ReportOpts
ropts' = ReportOpts
ropts { empty_ :: Bool
empty_=Bool
True, normalbalance_ :: Maybe NormalSign
normalbalance_=NormalSign -> Maybe NormalSign
forall a. a -> Maybe a
Just NormalSign
subreportnormalsign }
q :: Query
q = [Query] -> Query
And [Journal -> Query
subreportqfn Journal
j, Query
userq]
r :: PeriodicReport AccountName MixedAmount
r@(PeriodicReport [DateSpan]
dates [PeriodicReportRow AccountName MixedAmount]
rows PeriodicReportRow () MixedAmount
totals) = ReportOpts
-> Query
-> Journal
-> PriceOracle
-> PeriodicReport AccountName MixedAmount
multiBalanceReportWith ReportOpts
ropts' Query
q Journal
j PriceOracle
priceoracle
r' :: PeriodicReport AccountName MixedAmount
r' | Bool
empty_ = PeriodicReport AccountName MixedAmount
r
| Bool
otherwise = [DateSpan]
-> [PeriodicReportRow AccountName MixedAmount]
-> PeriodicReportRow () MixedAmount
-> PeriodicReport AccountName MixedAmount
forall a b.
[DateSpan]
-> [PeriodicReportRow a b]
-> PeriodicReportRow () b
-> PeriodicReport a b
PeriodicReport [DateSpan]
dates [PeriodicReportRow AccountName MixedAmount]
rows' PeriodicReportRow () MixedAmount
totals
where
nonzeroaccounts :: [AccountName]
nonzeroaccounts =
CommandDoc -> [AccountName] -> [AccountName]
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"nonzeroaccounts" ([AccountName] -> [AccountName]) -> [AccountName] -> [AccountName]
forall a b. (a -> b) -> a -> b
$
(PeriodicReportRow AccountName MixedAmount -> Maybe AccountName)
-> [PeriodicReportRow AccountName MixedAmount] -> [AccountName]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\(PeriodicReportRow AccountName
act Int
_ [MixedAmount]
amts MixedAmount
_ MixedAmount
_) ->
if Bool -> Bool
not ((MixedAmount -> Bool) -> [MixedAmount] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all MixedAmount -> Bool
mixedAmountLooksZero [MixedAmount]
amts) then AccountName -> Maybe AccountName
forall a. a -> Maybe a
Just AccountName
act else Maybe AccountName
forall a. Maybe a
Nothing) [PeriodicReportRow AccountName MixedAmount]
rows
rows' :: [PeriodicReportRow AccountName MixedAmount]
rows' = (PeriodicReportRow AccountName MixedAmount -> Bool)
-> [PeriodicReportRow AccountName MixedAmount]
-> [PeriodicReportRow AccountName MixedAmount]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (PeriodicReportRow AccountName MixedAmount -> Bool)
-> PeriodicReportRow AccountName MixedAmount
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicReportRow AccountName MixedAmount -> Bool
emptyRow) [PeriodicReportRow AccountName MixedAmount]
rows
where
emptyRow :: PeriodicReportRow AccountName MixedAmount -> Bool
emptyRow (PeriodicReportRow AccountName
act Int
_ [MixedAmount]
amts MixedAmount
_ MixedAmount
_) =
(MixedAmount -> Bool) -> [MixedAmount] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all MixedAmount -> Bool
mixedAmountLooksZero [MixedAmount]
amts Bool -> Bool -> Bool
&& Bool -> Bool
not ((AccountName -> Bool) -> [AccountName] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (AccountName
act AccountName -> AccountName -> Bool
`isAccountNamePrefixOf`) [AccountName]
nonzeroaccounts)
compoundBalanceReportAsText :: ReportOpts -> CompoundBalanceReport -> String
compoundBalanceReportAsText :: ReportOpts
-> (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> CommandDoc
compoundBalanceReportAsText ReportOpts
ropts (CommandDoc
title, [DateSpan]
_colspans, [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports, ([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
singlesubreport :: Bool
singlesubreport = [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
bigtable :: Table CommandDoc CommandDoc MixedAmount
bigtable =
case ((CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> Table CommandDoc CommandDoc MixedAmount)
-> [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
-> [Table CommandDoc CommandDoc MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map (ReportOpts
-> Bool
-> (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> Table CommandDoc CommandDoc MixedAmount
forall c.
ReportOpts
-> Bool
-> (CommandDoc, PeriodicReport AccountName MixedAmount, c)
-> Table CommandDoc CommandDoc MixedAmount
subreportAsTable ReportOpts
ropts Bool
singlesubreport) [(CommandDoc, PeriodicReport AccountName 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
|| Bool
singlesubreport =
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 [])
)
subreportAsTable :: ReportOpts
-> Bool
-> (CommandDoc, PeriodicReport AccountName MixedAmount, c)
-> Table CommandDoc CommandDoc MixedAmount
subreportAsTable ReportOpts
ropts Bool
singlesubreport (CommandDoc
title, PeriodicReport AccountName MixedAmount
r, c
_) = Table CommandDoc CommandDoc MixedAmount
t
where
ropts' :: ReportOpts
ropts' | Bool
singlesubreport = ReportOpts
ropts
| Bool
otherwise = ReportOpts
ropts{ no_total_ :: Bool
no_total_=Bool
False }
Table Header CommandDoc
lefthdrs Header CommandDoc
tophdrs [[MixedAmount]]
cells = ReportOpts
-> PeriodicReport AccountName MixedAmount
-> Table CommandDoc CommandDoc MixedAmount
balanceReportAsTable ReportOpts
ropts' PeriodicReport AccountName MixedAmount
r
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)
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')
compoundBalanceReportAsCsv :: ReportOpts -> CompoundBalanceReport -> CSV
compoundBalanceReportAsCsv :: ReportOpts
-> (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> CSV
compoundBalanceReportAsCsv ReportOpts
ropts (CommandDoc
title, [DateSpan]
colspans, [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports, ([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 AccountName MixedAmount, Bool) -> CSV)
-> [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
-> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ReportOpts
-> Bool
-> (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> CSV
forall c.
ReportOpts
-> Bool
-> (CommandDoc, PeriodicReport AccountName MixedAmount, c)
-> CSV
subreportAsCsv ReportOpts
ropts Bool
singlesubreport) [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports
where
singlesubreport :: Bool
singlesubreport = [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
subreportAsCsv :: ReportOpts
-> Bool
-> (CommandDoc, PeriodicReport AccountName MixedAmount, c)
-> CSV
subreportAsCsv ReportOpts
ropts Bool
singlesubreport (CommandDoc
subreporttitle, PeriodicReport AccountName 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 AccountName MixedAmount -> CSV
multiBalanceReportAsCsv ReportOpts
ropts' PeriodicReport AccountName MixedAmount
multibalreport)
where
ropts' :: ReportOpts
ropts' | Bool
singlesubreport = ReportOpts
ropts
| Bool
otherwise = ReportOpts
ropts{ no_total_ :: Bool
no_total_=Bool
False }
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 AccountName MixedAmount, Bool)]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(CommandDoc, PeriodicReport AccountName 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
$
(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
$
((CommandDoc, PeriodicReport AccountName MixedAmount, Bool) -> Int)
-> [(CommandDoc, PeriodicReport AccountName 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 AccountName MixedAmount, Bool)
-> [DateSpan])
-> (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicReport AccountName MixedAmount -> [DateSpan]
forall a b. PeriodicReport a b -> [DateSpan]
prDates (PeriodicReport AccountName MixedAmount -> [DateSpan])
-> ((CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> PeriodicReport AccountName MixedAmount)
-> (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> [DateSpan]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> PeriodicReport AccountName MixedAmount
forall a b c. (a, b, c) -> b
second3) [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports
addtotals :: CSV -> CSV
addtotals
| ReportOpts -> Bool
no_total_ ReportOpts
ropts Bool -> Bool -> Bool
|| [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, PeriodicReport AccountName 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 MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice (
[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 [])
)
])
compoundBalanceReportAsHtml :: ReportOpts -> CompoundBalanceReport -> Html ()
compoundBalanceReportAsHtml :: ReportOpts
-> (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
-> Html ()
compoundBalanceReportAsHtml ReportOpts
ropts (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
cbr =
let
(CommandDoc
title, [DateSpan]
colspans, [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports, ([MixedAmount]
coltotals, MixedAmount
grandtotal, MixedAmount
grandavg)) = (CommandDoc, [DateSpan],
[(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)],
([MixedAmount], MixedAmount, MixedAmount))
cbr
colspanattr :: Attribute
colspanattr = AccountName -> Attribute
colspan_ (AccountName -> Attribute) -> AccountName -> Attribute
forall a b. (a -> b) -> a -> b
$ CommandDoc -> AccountName
TS.pack (CommandDoc -> AccountName) -> CommandDoc -> AccountName
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 = AccountName -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ AccountName
"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)
subreportrows :: (String, MultiBalanceReport, Bool) -> [Html ()]
subreportrows :: (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> [Html ()]
subreportrows (CommandDoc
subreporttitle, PeriodicReport AccountName MixedAmount
mbr, Bool
_increasestotal) =
let
(Html ()
_,[Html ()]
bodyrows,Maybe (Html ())
mtotalsrow) = ReportOpts
-> PeriodicReport AccountName MixedAmount
-> (Html (), [Html ()], Maybe (Html ()))
multiBalanceReportHtmlRows ReportOpts
ropts PeriodicReport AccountName 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 AccountName MixedAmount, Bool)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = []
| Bool
otherwise =
let defstyle :: Attribute
defstyle = AccountName -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ AccountName
"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_ [AccountName -> Attribute
class_ AccountName
"", AccountName -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ AccountName
"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_ [AccountName -> Attribute
class_ AccountName
"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
$ MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice 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_ [AccountName -> Attribute
class_ AccountName
"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
$ MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice (MixedAmount -> CommandDoc) -> MixedAmount -> CommandDoc
forall a b. (a -> b) -> a -> b
$ 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_ [AccountName -> Attribute
class_ AccountName
"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
$ MixedAmount -> CommandDoc
showMixedAmountOneLineWithoutPrice (MixedAmount -> CommandDoc) -> MixedAmount -> CommandDoc
forall a b. (a -> b) -> a -> b
$ MixedAmount
grandavg] else [])
]
in do
AccountName -> Html ()
forall arg result. TermRaw arg result => arg -> result
style_ ([AccountName] -> AccountName
TS.unlines [AccountName
""
,AccountName
"td { padding:0 0.5em; }"
,AccountName
"td:nth-child(1) { white-space:nowrap; }"
,AccountName
"tr:nth-child(even) td { background-color:#eee; }"
])
[Attribute] -> Html ()
forall (m :: * -> *). Applicative m => [Attribute] -> HtmlT m ()
link_ [AccountName -> Attribute
rel_ AccountName
"stylesheet", AccountName -> Attribute
href_ AccountName
"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 AccountName MixedAmount, Bool)
-> [Html ()])
-> [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
-> [Html ()]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (CommandDoc, PeriodicReport AccountName MixedAmount, Bool)
-> [Html ()]
subreportrows [(CommandDoc, PeriodicReport AccountName MixedAmount, Bool)]
subreports
[Html ()] -> [Html ()] -> [Html ()]
forall a. [a] -> [a] -> [a]
++ [Html ()]
totalrows