{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module Hledger.Reports.BudgetReport (
BudgetGoal,
BudgetTotal,
BudgetAverage,
BudgetCell,
BudgetReportRow,
BudgetReport,
budgetReport,
budgetReportAsTable,
budgetReportAsText,
budgetReportAsCsv,
reportPeriodName,
combineBudgetAndActual,
tests_BudgetReport
)
where
import Data.Decimal (roundTo)
import Data.Default (def)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.List (nub, partition, transpose)
import Data.List.Extra (nubSort)
import Data.Maybe (fromMaybe)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid ((<>))
#endif
import Safe (headDef)
import qualified Data.Map as Map
import Data.Map (Map)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Text.Tabular as T
import Text.Tabular.AsciiWide as T
import Hledger.Data
import Hledger.Utils
import Hledger.Read.CsvReader (CSV)
import Hledger.Reports.ReportOptions
import Hledger.Reports.ReportTypes
import Hledger.Reports.MultiBalanceReport
type BudgetGoal = Change
type BudgetTotal = Total
type BudgetAverage = Average
type BudgetCell = (Maybe Change, Maybe BudgetGoal)
type BudgetReportRow = PeriodicReportRow DisplayName BudgetCell
type BudgetReport = PeriodicReport DisplayName BudgetCell
type BudgetDisplayCell = ((Text, Int), Maybe ((Text, Int), Maybe (Text, Int)))
budgetReport :: ReportSpec -> Bool -> DateSpan -> Journal -> BudgetReport
budgetReport :: ReportSpec -> Bool -> DateSpan -> Journal -> BudgetReport
budgetReport ReportSpec
rspec Bool
assrt DateSpan
reportspan Journal
j = String -> BudgetReport -> BudgetReport
forall a. Show a => String -> a -> a
dbg4 String
"sortedbudgetreport" BudgetReport
budgetreport
where
ropts :: ReportOpts
ropts = (ReportSpec -> ReportOpts
rsOpts ReportSpec
rspec){ accountlistmode_ :: AccountListMode
accountlistmode_ = AccountListMode
ALTree }
showunbudgeted :: Bool
showunbudgeted = ReportOpts -> Bool
empty_ ReportOpts
ropts
budgetedaccts :: [AccountName]
budgetedaccts =
String -> [AccountName] -> [AccountName]
forall a. Show a => String -> a -> a
dbg3 String
"budgetedacctsinperiod" ([AccountName] -> [AccountName]) -> [AccountName] -> [AccountName]
forall a b. (a -> b) -> a -> b
$
[AccountName] -> [AccountName]
forall a. Eq a => [a] -> [a]
nub ([AccountName] -> [AccountName]) -> [AccountName] -> [AccountName]
forall a b. (a -> b) -> a -> b
$
(AccountName -> [AccountName]) -> [AccountName] -> [AccountName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AccountName -> [AccountName]
expandAccountName ([AccountName] -> [AccountName]) -> [AccountName] -> [AccountName]
forall a b. (a -> b) -> a -> b
$
[Posting] -> [AccountName]
accountNamesFromPostings ([Posting] -> [AccountName]) -> [Posting] -> [AccountName]
forall a b. (a -> b) -> a -> b
$
(Transaction -> [Posting]) -> [Transaction] -> [Posting]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Transaction -> [Posting]
tpostings ([Transaction] -> [Posting]) -> [Transaction] -> [Posting]
forall a b. (a -> b) -> a -> b
$
(PeriodicTransaction -> [Transaction])
-> [PeriodicTransaction] -> [Transaction]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (PeriodicTransaction -> DateSpan -> [Transaction]
`runPeriodicTransaction` DateSpan
reportspan) ([PeriodicTransaction] -> [Transaction])
-> [PeriodicTransaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
Journal -> [PeriodicTransaction]
jperiodictxns Journal
j
actualj :: Journal
actualj = [AccountName] -> Bool -> Journal -> Journal
journalWithBudgetAccountNames [AccountName]
budgetedaccts Bool
showunbudgeted Journal
j
budgetj :: Journal
budgetj = Bool -> ReportOpts -> DateSpan -> Journal -> Journal
journalAddBudgetGoalTransactions Bool
assrt ReportOpts
ropts DateSpan
reportspan Journal
j
actualreport :: PeriodicReport DisplayName MixedAmount
actualreport@(PeriodicReport [DateSpan]
actualspans [PeriodicReportRow DisplayName MixedAmount]
_ PeriodicReportRow () MixedAmount
_) =
String
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a. Show a => String -> a -> a
dbg5 String
"actualreport" (PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount)
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PeriodicReport DisplayName MixedAmount
multiBalanceReport ReportSpec
rspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
ropts{empty_ :: Bool
empty_=Bool
True}} Journal
actualj
budgetgoalreport :: PeriodicReport DisplayName MixedAmount
budgetgoalreport@(PeriodicReport [DateSpan]
_ [PeriodicReportRow DisplayName MixedAmount]
budgetgoalitems PeriodicReportRow () MixedAmount
budgetgoaltotals) =
String
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a. Show a => String -> a -> a
dbg5 String
"budgetgoalreport" (PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount)
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PeriodicReport DisplayName MixedAmount
multiBalanceReport ReportSpec
rspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
ropts{empty_ :: Bool
empty_=Bool
True}} Journal
budgetj
budgetgoalreport' :: PeriodicReport DisplayName MixedAmount
budgetgoalreport'
| ReportOpts -> Interval
interval_ ReportOpts
ropts Interval -> Interval -> Bool
forall a. Eq a => a -> a -> Bool
== Interval
NoInterval = [DateSpan]
-> [PeriodicReportRow DisplayName MixedAmount]
-> PeriodicReportRow () MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a b.
[DateSpan]
-> [PeriodicReportRow a b]
-> PeriodicReportRow () b
-> PeriodicReport a b
PeriodicReport [DateSpan]
actualspans [PeriodicReportRow DisplayName MixedAmount]
budgetgoalitems PeriodicReportRow () MixedAmount
budgetgoaltotals
| Bool
otherwise = PeriodicReport DisplayName MixedAmount
budgetgoalreport
budgetreport :: BudgetReport
budgetreport = ReportOpts
-> Journal
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
-> BudgetReport
combineBudgetAndActual ReportOpts
ropts Journal
j PeriodicReport DisplayName MixedAmount
budgetgoalreport' PeriodicReport DisplayName MixedAmount
actualreport
journalAddBudgetGoalTransactions :: Bool -> ReportOpts -> DateSpan -> Journal -> Journal
journalAddBudgetGoalTransactions :: Bool -> ReportOpts -> DateSpan -> Journal -> Journal
journalAddBudgetGoalTransactions Bool
assrt ReportOpts
_ropts DateSpan
reportspan Journal
j =
(String -> Journal)
-> (Journal -> Journal) -> Either String Journal -> Journal
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Journal
forall a. String -> a
error' Journal -> Journal
forall a. a -> a
id (Either String Journal -> Journal)
-> Either String Journal -> Journal
forall a b. (a -> b) -> a -> b
$ Bool -> Journal -> Either String Journal
journalBalanceTransactions Bool
assrt Journal
j{ jtxns :: [Transaction]
jtxns = [Transaction]
budgetts }
where
budgetspan :: DateSpan
budgetspan = String -> DateSpan -> DateSpan
forall a. Show a => String -> a -> a
dbg3 String
"budget span" (DateSpan -> DateSpan) -> DateSpan -> DateSpan
forall a b. (a -> b) -> a -> b
$ DateSpan
reportspan
budgetts :: [Transaction]
budgetts =
String -> [Transaction] -> [Transaction]
forall a. Show a => String -> a -> a
dbg5 String
"budget goal txns" ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
[Transaction -> Transaction
makeBudgetTxn Transaction
t
| PeriodicTransaction
pt <- Journal -> [PeriodicTransaction]
jperiodictxns Journal
j
, Transaction
t <- PeriodicTransaction -> DateSpan -> [Transaction]
runPeriodicTransaction PeriodicTransaction
pt DateSpan
budgetspan
]
makeBudgetTxn :: Transaction -> Transaction
makeBudgetTxn Transaction
t = Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ Transaction
t { tdescription :: AccountName
tdescription = String -> AccountName
T.pack String
"Budget transaction" }
journalWithBudgetAccountNames :: [AccountName] -> Bool -> Journal -> Journal
journalWithBudgetAccountNames :: [AccountName] -> Bool -> Journal -> Journal
journalWithBudgetAccountNames [AccountName]
budgetedaccts Bool
showunbudgeted Journal
j =
(Journal -> String) -> Journal -> Journal
forall a. Show a => (a -> String) -> a -> a
dbg5With ((String
"budget account names: "String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String) -> (Journal -> String) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[AccountName] -> String
forall a. Show a => a -> String
pshow([AccountName] -> String)
-> (Journal -> [AccountName]) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Journal -> [AccountName]
journalAccountNamesUsed) (Journal -> Journal) -> Journal -> Journal
forall a b. (a -> b) -> a -> b
$
Journal
j { jtxns :: [Transaction]
jtxns = Transaction -> Transaction
remapTxn (Transaction -> Transaction) -> [Transaction] -> [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Journal -> [Transaction]
jtxns Journal
j }
where
remapTxn :: Transaction -> Transaction
remapTxn = ([Posting] -> [Posting]) -> Transaction -> Transaction
mapPostings ((Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Posting
remapPosting)
where
mapPostings :: ([Posting] -> [Posting]) -> Transaction -> Transaction
mapPostings [Posting] -> [Posting]
f Transaction
t = Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ Transaction
t { tpostings :: [Posting]
tpostings = [Posting] -> [Posting]
f ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t }
remapPosting :: Posting -> Posting
remapPosting Posting
p = Posting
p { paccount :: AccountName
paccount = AccountName -> AccountName
remapAccount (AccountName -> AccountName) -> AccountName -> AccountName
forall a b. (a -> b) -> a -> b
$ Posting -> AccountName
paccount Posting
p, poriginal :: Maybe Posting
poriginal = Posting -> Maybe Posting
forall a. a -> Maybe a
Just (Posting -> Maybe Posting)
-> (Maybe Posting -> Posting) -> Maybe Posting -> Maybe Posting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> Maybe Posting -> Posting
forall a. a -> Maybe a -> a
fromMaybe Posting
p (Maybe Posting -> Maybe Posting) -> Maybe Posting -> Maybe Posting
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Posting
poriginal Posting
p }
where
remapAccount :: AccountName -> AccountName
remapAccount AccountName
a
| Bool
hasbudget = AccountName
a
| Bool
hasbudgetedparent = if Bool
showunbudgeted then AccountName
a else AccountName
budgetedparent
| Bool
otherwise = if Bool
showunbudgeted then AccountName
u AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
acctsep AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
a else AccountName
u
where
hasbudget :: Bool
hasbudget = AccountName
a AccountName -> [AccountName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [AccountName]
budgetedaccts
hasbudgetedparent :: Bool
hasbudgetedparent = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ AccountName -> Bool
T.null AccountName
budgetedparent
budgetedparent :: AccountName
budgetedparent = AccountName -> [AccountName] -> AccountName
forall a. a -> [a] -> a
headDef AccountName
"" ([AccountName] -> AccountName) -> [AccountName] -> AccountName
forall a b. (a -> b) -> a -> b
$ (AccountName -> Bool) -> [AccountName] -> [AccountName]
forall a. (a -> Bool) -> [a] -> [a]
filter (AccountName -> [AccountName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [AccountName]
budgetedaccts) ([AccountName] -> [AccountName]) -> [AccountName] -> [AccountName]
forall a b. (a -> b) -> a -> b
$ AccountName -> [AccountName]
parentAccountNames AccountName
a
u :: AccountName
u = AccountName
unbudgetedAccountName
combineBudgetAndActual :: ReportOpts -> Journal -> MultiBalanceReport -> MultiBalanceReport -> BudgetReport
combineBudgetAndActual :: ReportOpts
-> Journal
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
-> BudgetReport
combineBudgetAndActual ReportOpts
ropts Journal
j
(PeriodicReport [DateSpan]
budgetperiods [PeriodicReportRow DisplayName MixedAmount]
budgetrows (PeriodicReportRow ()
_ [MixedAmount]
budgettots MixedAmount
budgetgrandtot MixedAmount
budgetgrandavg))
(PeriodicReport [DateSpan]
actualperiods [PeriodicReportRow DisplayName MixedAmount]
actualrows (PeriodicReportRow ()
_ [MixedAmount]
actualtots MixedAmount
actualgrandtot MixedAmount
actualgrandavg)) =
[DateSpan]
-> [PeriodicReportRow DisplayName BudgetCell]
-> PeriodicReportRow () BudgetCell
-> BudgetReport
forall a b.
[DateSpan]
-> [PeriodicReportRow a b]
-> PeriodicReportRow () b
-> PeriodicReport a b
PeriodicReport [DateSpan]
periods [PeriodicReportRow DisplayName BudgetCell]
sortedrows PeriodicReportRow () BudgetCell
totalrow
where
periods :: [DateSpan]
periods = [DateSpan] -> [DateSpan]
forall a. Ord a => [a] -> [a]
nubSort ([DateSpan] -> [DateSpan])
-> ([DateSpan] -> [DateSpan]) -> [DateSpan] -> [DateSpan]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DateSpan -> Bool) -> [DateSpan] -> [DateSpan]
forall a. (a -> Bool) -> [a] -> [a]
filter (DateSpan -> DateSpan -> Bool
forall a. Eq a => a -> a -> Bool
/= DateSpan
nulldatespan) ([DateSpan] -> [DateSpan]) -> [DateSpan] -> [DateSpan]
forall a b. (a -> b) -> a -> b
$ [DateSpan]
budgetperiods [DateSpan] -> [DateSpan] -> [DateSpan]
forall a. [a] -> [a] -> [a]
++ [DateSpan]
actualperiods
rows1 :: [PeriodicReportRow DisplayName BudgetCell]
rows1 =
[ DisplayName
-> [BudgetCell]
-> BudgetCell
-> BudgetCell
-> PeriodicReportRow DisplayName BudgetCell
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow DisplayName
acct [BudgetCell]
amtandgoals BudgetCell
totamtandgoal BudgetCell
avgamtandgoal
| PeriodicReportRow DisplayName
acct [MixedAmount]
actualamts MixedAmount
actualtot MixedAmount
actualavg <- [PeriodicReportRow DisplayName MixedAmount]
actualrows
, let mbudgetgoals :: Maybe ([MixedAmount], MixedAmount, MixedAmount)
mbudgetgoals = AccountName
-> HashMap AccountName ([MixedAmount], MixedAmount, MixedAmount)
-> Maybe ([MixedAmount], MixedAmount, MixedAmount)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup (DisplayName -> AccountName
displayFull DisplayName
acct) HashMap AccountName ([MixedAmount], MixedAmount, MixedAmount)
budgetGoalsByAcct :: Maybe ([BudgetGoal], BudgetTotal, BudgetAverage)
, let budgetmamts :: [Maybe MixedAmount]
budgetmamts = [Maybe MixedAmount]
-> (([MixedAmount], MixedAmount, MixedAmount)
-> [Maybe MixedAmount])
-> Maybe ([MixedAmount], MixedAmount, MixedAmount)
-> [Maybe MixedAmount]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe MixedAmount
forall a. Maybe a
Nothing Maybe MixedAmount -> [DateSpan] -> [Maybe MixedAmount]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [DateSpan]
periods) ((MixedAmount -> Maybe MixedAmount)
-> [MixedAmount] -> [Maybe MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just ([MixedAmount] -> [Maybe MixedAmount])
-> (([MixedAmount], MixedAmount, MixedAmount) -> [MixedAmount])
-> ([MixedAmount], MixedAmount, MixedAmount)
-> [Maybe MixedAmount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([MixedAmount], MixedAmount, MixedAmount) -> [MixedAmount]
forall a b c. (a, b, c) -> a
first3) Maybe ([MixedAmount], MixedAmount, MixedAmount)
mbudgetgoals :: [Maybe BudgetGoal]
, let mbudgettot :: Maybe MixedAmount
mbudgettot = ([MixedAmount], MixedAmount, MixedAmount) -> MixedAmount
forall a b c. (a, b, c) -> b
second3 (([MixedAmount], MixedAmount, MixedAmount) -> MixedAmount)
-> Maybe ([MixedAmount], MixedAmount, MixedAmount)
-> Maybe MixedAmount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ([MixedAmount], MixedAmount, MixedAmount)
mbudgetgoals :: Maybe BudgetTotal
, let mbudgetavg :: Maybe MixedAmount
mbudgetavg = ([MixedAmount], MixedAmount, MixedAmount) -> MixedAmount
forall a b c. (a, b, c) -> c
third3 (([MixedAmount], MixedAmount, MixedAmount) -> MixedAmount)
-> Maybe ([MixedAmount], MixedAmount, MixedAmount)
-> Maybe MixedAmount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ([MixedAmount], MixedAmount, MixedAmount)
mbudgetgoals :: Maybe BudgetAverage
, let acctBudgetByPeriod :: Map DateSpan MixedAmount
acctBudgetByPeriod = [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (DateSpan
p,MixedAmount
budgetamt) | (DateSpan
p, Just MixedAmount
budgetamt) <- [DateSpan]
-> [Maybe MixedAmount] -> [(DateSpan, Maybe MixedAmount)]
forall a b. [a] -> [b] -> [(a, b)]
zip [DateSpan]
budgetperiods [Maybe MixedAmount]
budgetmamts ] :: Map DateSpan BudgetGoal
, let acctActualByPeriod :: Map DateSpan MixedAmount
acctActualByPeriod = [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (DateSpan
p,MixedAmount
actualamt) | (DateSpan
p, Just MixedAmount
actualamt) <- [DateSpan]
-> [Maybe MixedAmount] -> [(DateSpan, Maybe MixedAmount)]
forall a b. [a] -> [b] -> [(a, b)]
zip [DateSpan]
actualperiods ((MixedAmount -> Maybe MixedAmount)
-> [MixedAmount] -> [Maybe MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just [MixedAmount]
actualamts) ] :: Map DateSpan Change
, let amtandgoals :: [BudgetCell]
amtandgoals = [ (DateSpan -> Map DateSpan MixedAmount -> Maybe MixedAmount
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup DateSpan
p Map DateSpan MixedAmount
acctActualByPeriod, DateSpan -> Map DateSpan MixedAmount -> Maybe MixedAmount
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup DateSpan
p Map DateSpan MixedAmount
acctBudgetByPeriod) | DateSpan
p <- [DateSpan]
periods ] :: [BudgetCell]
, let totamtandgoal :: BudgetCell
totamtandgoal = (MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
actualtot, Maybe MixedAmount
mbudgettot)
, let avgamtandgoal :: BudgetCell
avgamtandgoal = (MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
actualavg, Maybe MixedAmount
mbudgetavg)
]
where
HashMap AccountName ([MixedAmount], MixedAmount, MixedAmount)
budgetGoalsByAcct :: HashMap AccountName ([BudgetGoal], BudgetTotal, BudgetAverage) =
[(AccountName, ([MixedAmount], MixedAmount, MixedAmount))]
-> HashMap AccountName ([MixedAmount], MixedAmount, MixedAmount)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList [ (DisplayName -> AccountName
displayFull DisplayName
acct, ([MixedAmount]
amts, MixedAmount
tot, MixedAmount
avg))
| PeriodicReportRow DisplayName
acct [MixedAmount]
amts MixedAmount
tot MixedAmount
avg <- [PeriodicReportRow DisplayName MixedAmount]
budgetrows ]
rows2 :: [PeriodicReportRow DisplayName BudgetCell]
rows2 =
[ DisplayName
-> [BudgetCell]
-> BudgetCell
-> BudgetCell
-> PeriodicReportRow DisplayName BudgetCell
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow DisplayName
acct [BudgetCell]
amtandgoals BudgetCell
forall a. (Maybe a, Maybe MixedAmount)
totamtandgoal BudgetCell
forall a. (Maybe a, Maybe MixedAmount)
avgamtandgoal
| PeriodicReportRow DisplayName
acct [MixedAmount]
budgetgoals MixedAmount
budgettot MixedAmount
budgetavg <- [PeriodicReportRow DisplayName MixedAmount]
budgetrows
, DisplayName -> AccountName
displayFull DisplayName
acct AccountName -> [AccountName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (PeriodicReportRow DisplayName BudgetCell -> AccountName)
-> [PeriodicReportRow DisplayName BudgetCell] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName BudgetCell -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrFullName [PeriodicReportRow DisplayName BudgetCell]
rows1
, let acctBudgetByPeriod :: Map DateSpan MixedAmount
acctBudgetByPeriod = [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount)
-> [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall a b. (a -> b) -> a -> b
$ [DateSpan] -> [MixedAmount] -> [(DateSpan, MixedAmount)]
forall a b. [a] -> [b] -> [(a, b)]
zip [DateSpan]
budgetperiods [MixedAmount]
budgetgoals :: Map DateSpan BudgetGoal
, let amtandgoals :: [BudgetCell]
amtandgoals = [ (Maybe MixedAmount
forall a. Maybe a
Nothing, DateSpan -> Map DateSpan MixedAmount -> Maybe MixedAmount
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup DateSpan
p Map DateSpan MixedAmount
acctBudgetByPeriod) | DateSpan
p <- [DateSpan]
periods ] :: [BudgetCell]
, let totamtandgoal :: (Maybe a, Maybe MixedAmount)
totamtandgoal = (Maybe a
forall a. Maybe a
Nothing, MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
budgettot)
, let avgamtandgoal :: (Maybe a, Maybe MixedAmount)
avgamtandgoal = (Maybe a
forall a. Maybe a
Nothing, MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
budgetavg)
]
[PeriodicReportRow DisplayName BudgetCell]
sortedrows :: [BudgetReportRow] = [AccountName]
-> [PeriodicReportRow DisplayName BudgetCell]
-> [PeriodicReportRow DisplayName BudgetCell]
forall b.
[AccountName]
-> [PeriodicReportRow DisplayName b]
-> [PeriodicReportRow DisplayName b]
sortRowsLike ([PeriodicReportRow DisplayName BudgetCell] -> [AccountName]
forall b.
[PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [AccountName]
mbrsorted [PeriodicReportRow DisplayName BudgetCell]
unbudgetedrows [AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ [PeriodicReportRow DisplayName BudgetCell] -> [AccountName]
forall b.
[PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [AccountName]
mbrsorted [PeriodicReportRow DisplayName BudgetCell]
rows') [PeriodicReportRow DisplayName BudgetCell]
rows
where
([PeriodicReportRow DisplayName BudgetCell]
unbudgetedrows, [PeriodicReportRow DisplayName BudgetCell]
rows') = (PeriodicReportRow DisplayName BudgetCell -> Bool)
-> [PeriodicReportRow DisplayName BudgetCell]
-> ([PeriodicReportRow DisplayName BudgetCell],
[PeriodicReportRow DisplayName BudgetCell])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((AccountName -> AccountName -> Bool
forall a. Eq a => a -> a -> Bool
==AccountName
unbudgetedAccountName) (AccountName -> Bool)
-> (PeriodicReportRow DisplayName BudgetCell -> AccountName)
-> PeriodicReportRow DisplayName BudgetCell
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicReportRow DisplayName BudgetCell -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrFullName) [PeriodicReportRow DisplayName BudgetCell]
rows
mbrsorted :: [PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [AccountName]
mbrsorted = (PeriodicReportRow DisplayName MixedAmount -> AccountName)
-> [PeriodicReportRow DisplayName MixedAmount] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrFullName ([PeriodicReportRow DisplayName MixedAmount] -> [AccountName])
-> ([PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [PeriodicReportRow DisplayName MixedAmount])
-> [PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [AccountName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts
-> Journal
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortRows ReportOpts
ropts Journal
j ([PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount])
-> ([PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [PeriodicReportRow DisplayName MixedAmount])
-> [PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [PeriodicReportRow DisplayName MixedAmount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PeriodicReportRow DisplayName (Maybe MixedAmount, b)
-> PeriodicReportRow DisplayName MixedAmount)
-> [PeriodicReportRow DisplayName (Maybe MixedAmount, b)]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map (((Maybe MixedAmount, b) -> MixedAmount)
-> PeriodicReportRow DisplayName (Maybe MixedAmount, b)
-> PeriodicReportRow DisplayName MixedAmount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Maybe MixedAmount, b) -> MixedAmount)
-> PeriodicReportRow DisplayName (Maybe MixedAmount, b)
-> PeriodicReportRow DisplayName MixedAmount)
-> ((Maybe MixedAmount, b) -> MixedAmount)
-> PeriodicReportRow DisplayName (Maybe MixedAmount, b)
-> PeriodicReportRow DisplayName MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount -> Maybe MixedAmount -> MixedAmount
forall a. a -> Maybe a -> a
fromMaybe MixedAmount
0 (Maybe MixedAmount -> MixedAmount)
-> ((Maybe MixedAmount, b) -> Maybe MixedAmount)
-> (Maybe MixedAmount, b)
-> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe MixedAmount, b) -> Maybe MixedAmount
forall a b. (a, b) -> a
fst)
rows :: [PeriodicReportRow DisplayName BudgetCell]
rows = [PeriodicReportRow DisplayName BudgetCell]
rows1 [PeriodicReportRow DisplayName BudgetCell]
-> [PeriodicReportRow DisplayName BudgetCell]
-> [PeriodicReportRow DisplayName BudgetCell]
forall a. [a] -> [a] -> [a]
++ [PeriodicReportRow DisplayName BudgetCell]
rows2
totalrow :: PeriodicReportRow () BudgetCell
totalrow = ()
-> [BudgetCell]
-> BudgetCell
-> BudgetCell
-> PeriodicReportRow () BudgetCell
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow ()
[ (DateSpan -> Map DateSpan MixedAmount -> Maybe MixedAmount
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup DateSpan
p Map DateSpan MixedAmount
totActualByPeriod, DateSpan -> Map DateSpan MixedAmount -> Maybe MixedAmount
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup DateSpan
p Map DateSpan MixedAmount
totBudgetByPeriod) | DateSpan
p <- [DateSpan]
periods ]
( MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
actualgrandtot, MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
budgetgrandtot )
( MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
actualgrandavg, MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
budgetgrandavg )
where
totBudgetByPeriod :: Map DateSpan MixedAmount
totBudgetByPeriod = [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount)
-> [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall a b. (a -> b) -> a -> b
$ [DateSpan] -> [MixedAmount] -> [(DateSpan, MixedAmount)]
forall a b. [a] -> [b] -> [(a, b)]
zip [DateSpan]
budgetperiods [MixedAmount]
budgettots :: Map DateSpan BudgetTotal
totActualByPeriod :: Map DateSpan MixedAmount
totActualByPeriod = [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount)
-> [(DateSpan, MixedAmount)] -> Map DateSpan MixedAmount
forall a b. (a -> b) -> a -> b
$ [DateSpan] -> [MixedAmount] -> [(DateSpan, MixedAmount)]
forall a b. [a] -> [b] -> [(a, b)]
zip [DateSpan]
actualperiods [MixedAmount]
actualtots :: Map DateSpan Change
budgetReportAsText :: ReportOpts -> BudgetReport -> TL.Text
budgetReportAsText :: ReportOpts -> BudgetReport -> Text
budgetReportAsText ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[AccountName]
[Status]
Maybe Int
Maybe NormalSign
Maybe DateSpan
Maybe ValuationType
Interval
Period
StringFormat
Costing
AccountListMode
BalanceType
ReportType
transpose_ :: ReportOpts -> Bool
forecast_ :: ReportOpts -> Maybe DateSpan
color_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
invert_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
pretty_tables_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
drop_ :: ReportOpts -> Int
balancetype_ :: ReportOpts -> BalanceType
reporttype_ :: ReportOpts -> ReportType
txn_dates_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
average_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [AccountName]
format_ :: ReportOpts -> StringFormat
real_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
date2_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
infer_value_ :: ReportOpts -> Bool
value_ :: ReportOpts -> Maybe ValuationType
cost_ :: ReportOpts -> Costing
statuses_ :: ReportOpts -> [Status]
period_ :: ReportOpts -> Period
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
reporttype_ :: ReportType
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [AccountName]
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_value_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
interval_ :: ReportOpts -> Interval
empty_ :: ReportOpts -> Bool
accountlistmode_ :: ReportOpts -> AccountListMode
..} BudgetReport
budgetr = Builder -> Text
TB.toLazyText (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$
AccountName -> Builder
TB.fromText AccountName
title Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> AccountName -> Builder
TB.fromText AccountName
"\n\n" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<>
TableOpts
-> (AccountName -> Cell)
-> (AccountName -> Cell)
-> (((Int, Int, Int), BudgetDisplayCell) -> Cell)
-> Table
AccountName AccountName ((Int, Int, Int), BudgetDisplayCell)
-> Builder
forall rh ch a.
TableOpts
-> (rh -> Cell)
-> (ch -> Cell)
-> (a -> Cell)
-> Table rh ch a
-> Builder
renderTableB TableOpts
forall a. Default a => a
def{tableBorders :: Bool
tableBorders=Bool
False,prettyTable :: Bool
prettyTable=Bool
pretty_tables_}
(Align -> AccountName -> Cell
textCell Align
TopLeft) (Align -> AccountName -> Cell
textCell Align
TopRight) (((Int, Int, Int) -> BudgetDisplayCell -> Cell)
-> ((Int, Int, Int), BudgetDisplayCell) -> Cell
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (Int, Int, Int) -> BudgetDisplayCell -> Cell
showcell) Table AccountName AccountName ((Int, Int, Int), BudgetDisplayCell)
displayTableWithWidths
where
title :: AccountName
title = AccountName
"Budget performance in " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> DateSpan -> AccountName
showDateSpan (BudgetReport -> DateSpan
forall a b. PeriodicReport a b -> DateSpan
periodicReportSpan BudgetReport
budgetr)
AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> (case Costing
cost_ of
Costing
Cost -> AccountName
", converted to cost"
Costing
NoCost -> AccountName
"")
AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> (case Maybe ValuationType
value_ of
Just (AtThen Maybe AccountName
_mc) -> AccountName
", valued at posting date"
Just (AtEnd Maybe AccountName
_mc) -> AccountName
", valued at period ends"
Just (AtNow Maybe AccountName
_mc) -> AccountName
", current value"
Just (AtDate Day
d Maybe AccountName
_mc) -> AccountName
", valued at " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> Day -> AccountName
showDate Day
d
Maybe ValuationType
Nothing -> AccountName
"")
AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
":"
displayTableWithWidths :: Table Text Text ((Int, Int, Int), BudgetDisplayCell)
displayTableWithWidths :: Table AccountName AccountName ((Int, Int, Int), BudgetDisplayCell)
displayTableWithWidths = Header AccountName
-> Header AccountName
-> [[((Int, Int, Int), BudgetDisplayCell)]]
-> Table
AccountName AccountName ((Int, Int, Int), BudgetDisplayCell)
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table Header AccountName
rh Header AccountName
ch ([[((Int, Int, Int), BudgetDisplayCell)]]
-> Table
AccountName AccountName ((Int, Int, Int), BudgetDisplayCell))
-> [[((Int, Int, Int), BudgetDisplayCell)]]
-> Table
AccountName AccountName ((Int, Int, Int), BudgetDisplayCell)
forall a b. (a -> b) -> a -> b
$ ([BudgetDisplayCell] -> [((Int, Int, Int), BudgetDisplayCell)])
-> [[BudgetDisplayCell]]
-> [[((Int, Int, Int), BudgetDisplayCell)]]
forall a b. (a -> b) -> [a] -> [b]
map (((Int, Int, Int)
-> BudgetDisplayCell -> ((Int, Int, Int), BudgetDisplayCell))
-> [(Int, Int, Int)]
-> [BudgetDisplayCell]
-> [((Int, Int, Int), BudgetDisplayCell)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (,) [(Int, Int, Int)]
widths) [[BudgetDisplayCell]]
displaycells
Table Header AccountName
rh Header AccountName
ch [[BudgetDisplayCell]]
displaycells = case ReportOpts
-> BudgetReport -> Table AccountName AccountName BudgetCell
budgetReportAsTable ReportOpts
ropts BudgetReport
budgetr of
Table Header AccountName
rh' Header AccountName
ch' [[BudgetCell]]
vals -> Table AccountName AccountName BudgetDisplayCell
-> Table AccountName AccountName BudgetDisplayCell
forall rh a. Table rh rh a -> Table rh rh a
maybetranspose (Table AccountName AccountName BudgetDisplayCell
-> Table AccountName AccountName BudgetDisplayCell)
-> ([[BudgetDisplayCell]]
-> Table AccountName AccountName BudgetDisplayCell)
-> [[BudgetDisplayCell]]
-> Table AccountName AccountName BudgetDisplayCell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header AccountName
-> Header AccountName
-> [[BudgetDisplayCell]]
-> Table AccountName AccountName BudgetDisplayCell
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table Header AccountName
rh' Header AccountName
ch' ([[BudgetDisplayCell]]
-> Table AccountName AccountName BudgetDisplayCell)
-> [[BudgetDisplayCell]]
-> Table AccountName AccountName BudgetDisplayCell
forall a b. (a -> b) -> a -> b
$ ([BudgetCell] -> [BudgetDisplayCell])
-> [[BudgetCell]] -> [[BudgetDisplayCell]]
forall a b. (a -> b) -> [a] -> [b]
map ((BudgetCell -> BudgetDisplayCell)
-> [BudgetCell] -> [BudgetDisplayCell]
forall a b. (a -> b) -> [a] -> [b]
map BudgetCell -> BudgetDisplayCell
forall (f :: * -> *).
Functor f =>
(Maybe MixedAmount, f MixedAmount)
-> ((AccountName, Int),
f ((AccountName, Int), Maybe (AccountName, Int)))
displayCell) [[BudgetCell]]
vals
displayCell :: (Maybe MixedAmount, f MixedAmount)
-> ((AccountName, Int),
f ((AccountName, Int), Maybe (AccountName, Int)))
displayCell (Maybe MixedAmount
actual, f MixedAmount
budget) = (MixedAmount -> (AccountName, Int)
showamt MixedAmount
actual', MixedAmount -> ((AccountName, Int), Maybe (AccountName, Int))
budgetAndPerc (MixedAmount -> ((AccountName, Int), Maybe (AccountName, Int)))
-> f MixedAmount
-> f ((AccountName, Int), Maybe (AccountName, Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f MixedAmount
budget)
where
actual' :: MixedAmount
actual' = MixedAmount -> Maybe MixedAmount -> MixedAmount
forall a. a -> Maybe a -> a
fromMaybe MixedAmount
0 Maybe MixedAmount
actual
budgetAndPerc :: MixedAmount -> ((AccountName, Int), Maybe (AccountName, Int))
budgetAndPerc MixedAmount
b = (MixedAmount -> (AccountName, Int)
showamt MixedAmount
b, DecimalRaw Integer -> (AccountName, Int)
forall i.
(Integral i, Show i) =>
DecimalRaw i -> (AccountName, Int)
showper (DecimalRaw Integer -> (AccountName, Int))
-> Maybe (DecimalRaw Integer) -> Maybe (AccountName, Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MixedAmount -> MixedAmount -> Maybe (DecimalRaw Integer)
percentage MixedAmount
actual' MixedAmount
b)
showamt :: MixedAmount -> (AccountName, Int)
showamt = (\(WideBuilder Builder
b Int
w) -> (Text -> AccountName
TL.toStrict (Text -> AccountName) -> Text -> AccountName
forall a b. (a -> b) -> a -> b
$ Builder -> Text
TB.toLazyText Builder
b, Int
w)) (WideBuilder -> (AccountName, Int))
-> (MixedAmount -> WideBuilder)
-> MixedAmount
-> (AccountName, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
oneLine{displayColour :: Bool
displayColour=Bool
color_, displayMaxWidth :: Maybe Int
displayMaxWidth=Int -> Maybe Int
forall a. a -> Maybe a
Just Int
32}
showper :: DecimalRaw i -> (AccountName, Int)
showper DecimalRaw i
p = let str :: AccountName
str = String -> AccountName
T.pack (DecimalRaw i -> String
forall a. Show a => a -> String
show (DecimalRaw i -> String) -> DecimalRaw i -> String
forall a b. (a -> b) -> a -> b
$ Word8 -> DecimalRaw i -> DecimalRaw i
forall i. Integral i => Word8 -> DecimalRaw i -> DecimalRaw i
roundTo Word8
0 DecimalRaw i
p) in (AccountName
str, AccountName -> Int
T.length AccountName
str)
cellWidth :: ((a, a), Maybe ((a, b), Maybe (a, c))) -> (a, b, c)
cellWidth ((a
_,a
wa), Maybe ((a, b), Maybe (a, c))
Nothing) = (a
wa, b
0, c
0)
cellWidth ((a
_,a
wa), Just ((a
_,b
wb), Maybe (a, c)
Nothing)) = (a
wa, b
wb, c
0)
cellWidth ((a
_,a
wa), Just ((a
_,b
wb), Just (a
_,c
wp))) = (a
wa, b
wb, c
wp)
widths :: [(Int, Int, Int)]
widths = [Int] -> [Int] -> [Int] -> [(Int, Int, Int)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Int]
actualwidths [Int]
budgetwidths [Int]
percentwidths
actualwidths :: [Int]
actualwidths = ([BudgetDisplayCell] -> Int) -> [[BudgetDisplayCell]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> Int
forall a. Integral a => [a] -> a
maximum' ([Int] -> Int)
-> ([BudgetDisplayCell] -> [Int]) -> [BudgetDisplayCell] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BudgetDisplayCell -> Int) -> [BudgetDisplayCell] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int, Int) -> Int
forall a b c. (a, b, c) -> a
first3 ((Int, Int, Int) -> Int)
-> (BudgetDisplayCell -> (Int, Int, Int))
-> BudgetDisplayCell
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BudgetDisplayCell -> (Int, Int, Int)
forall b c a a a a.
(Num b, Num c) =>
((a, a), Maybe ((a, b), Maybe (a, c))) -> (a, b, c)
cellWidth)) [[BudgetDisplayCell]]
cols
budgetwidths :: [Int]
budgetwidths = ([BudgetDisplayCell] -> Int) -> [[BudgetDisplayCell]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> Int
forall a. Integral a => [a] -> a
maximum' ([Int] -> Int)
-> ([BudgetDisplayCell] -> [Int]) -> [BudgetDisplayCell] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BudgetDisplayCell -> Int) -> [BudgetDisplayCell] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int, Int) -> Int
forall a b c. (a, b, c) -> b
second3 ((Int, Int, Int) -> Int)
-> (BudgetDisplayCell -> (Int, Int, Int))
-> BudgetDisplayCell
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BudgetDisplayCell -> (Int, Int, Int)
forall b c a a a a.
(Num b, Num c) =>
((a, a), Maybe ((a, b), Maybe (a, c))) -> (a, b, c)
cellWidth)) [[BudgetDisplayCell]]
cols
percentwidths :: [Int]
percentwidths = ([BudgetDisplayCell] -> Int) -> [[BudgetDisplayCell]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> Int
forall a. Integral a => [a] -> a
maximum' ([Int] -> Int)
-> ([BudgetDisplayCell] -> [Int]) -> [BudgetDisplayCell] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BudgetDisplayCell -> Int) -> [BudgetDisplayCell] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int, Int) -> Int
forall a b c. (a, b, c) -> c
third3 ((Int, Int, Int) -> Int)
-> (BudgetDisplayCell -> (Int, Int, Int))
-> BudgetDisplayCell
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BudgetDisplayCell -> (Int, Int, Int)
forall b c a a a a.
(Num b, Num c) =>
((a, a), Maybe ((a, b), Maybe (a, c))) -> (a, b, c)
cellWidth)) [[BudgetDisplayCell]]
cols
cols :: [[BudgetDisplayCell]]
cols = [[BudgetDisplayCell]] -> [[BudgetDisplayCell]]
forall a. [[a]] -> [[a]]
transpose [[BudgetDisplayCell]]
displaycells
showcell :: (Int, Int, Int) -> BudgetDisplayCell -> Cell
showcell :: (Int, Int, Int) -> BudgetDisplayCell -> Cell
showcell (Int
actualwidth, Int
budgetwidth, Int
percentwidth) ((AccountName
actual,Int
wa), Maybe ((AccountName, Int), Maybe (AccountName, Int))
mbudget) =
Align -> [WideBuilder] -> Cell
Cell Align
TopRight [Builder -> Int -> WideBuilder
WideBuilder ( AccountName -> Builder
TB.fromText (Int -> AccountName -> AccountName
T.replicate (Int
actualwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
wa) AccountName
" ")
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> AccountName -> Builder
TB.fromText AccountName
actual
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
budgetstr
) (Int
actualwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
totalbudgetwidth)]
where
totalpercentwidth :: Int
totalpercentwidth = if Int
percentwidth Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
0 else Int
percentwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5
totalbudgetwidth :: Int
totalbudgetwidth = if Int
budgetwidth Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
0 else Int
budgetwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
totalpercentwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3
budgetstr :: Builder
budgetstr = AccountName -> Builder
TB.fromText (AccountName -> Builder) -> AccountName -> Builder
forall a b. (a -> b) -> a -> b
$ case Maybe ((AccountName, Int), Maybe (AccountName, Int))
mbudget of
Maybe ((AccountName, Int), Maybe (AccountName, Int))
Nothing -> Int -> AccountName -> AccountName
T.replicate Int
totalbudgetwidth AccountName
" "
Just ((AccountName
budget, Int
wb), Maybe (AccountName, Int)
Nothing) -> AccountName
" [" AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> Int -> AccountName -> AccountName
T.replicate Int
totalpercentwidth AccountName
" " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> Int -> AccountName -> AccountName
T.replicate (Int
budgetwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
wb) AccountName
" " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
budget AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
"]"
Just ((AccountName
budget, Int
wb), Just (AccountName
pct, Int
wp)) -> AccountName
" [" AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> Int -> AccountName -> AccountName
T.replicate (Int
percentwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
wp) AccountName
" " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
pct AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
"% of " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> Int -> AccountName -> AccountName
T.replicate (Int
budgetwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
wb) AccountName
" " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
budget AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
"]"
percentage :: Change -> BudgetGoal -> Maybe Percentage
percentage :: MixedAmount -> MixedAmount -> Maybe (DecimalRaw Integer)
percentage MixedAmount
actual MixedAmount
budget =
case (MixedAmount -> MixedAmount
maybecost (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
normaliseMixedAmount MixedAmount
actual, MixedAmount -> MixedAmount
maybecost (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
normaliseMixedAmount MixedAmount
budget) of
(Mixed [Amount
a], Mixed [Amount
b]) | (Amount -> AccountName
acommodity Amount
a AccountName -> AccountName -> Bool
forall a. Eq a => a -> a -> Bool
== Amount -> AccountName
acommodity Amount
b Bool -> Bool -> Bool
|| Amount -> Bool
amountLooksZero Amount
a) Bool -> Bool -> Bool
&& Bool -> Bool
not (Amount -> Bool
amountLooksZero Amount
b)
-> DecimalRaw Integer -> Maybe (DecimalRaw Integer)
forall a. a -> Maybe a
Just (DecimalRaw Integer -> Maybe (DecimalRaw Integer))
-> DecimalRaw Integer -> Maybe (DecimalRaw Integer)
forall a b. (a -> b) -> a -> b
$ DecimalRaw Integer
100 DecimalRaw Integer -> DecimalRaw Integer -> DecimalRaw Integer
forall a. Num a => a -> a -> a
* Amount -> DecimalRaw Integer
aquantity Amount
a DecimalRaw Integer -> DecimalRaw Integer -> DecimalRaw Integer
forall a. Fractional a => a -> a -> a
/ Amount -> DecimalRaw Integer
aquantity Amount
b
(MixedAmount, MixedAmount)
_ ->
Maybe (DecimalRaw Integer)
forall a. Maybe a
Nothing
where
maybecost :: MixedAmount -> MixedAmount
maybecost = case Costing
cost_ of
Costing
Cost -> MixedAmount -> MixedAmount
mixedAmountCost
Costing
NoCost -> MixedAmount -> MixedAmount
forall a. a -> a
id
maybetranspose :: Table rh rh a -> Table rh rh a
maybetranspose | Bool
transpose_ = \(Table Header rh
rh Header rh
ch [[a]]
vals) -> Header rh -> Header rh -> [[a]] -> Table rh rh a
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table Header rh
ch Header rh
rh ([[a]] -> [[a]]
forall a. [[a]] -> [[a]]
transpose [[a]]
vals)
| Bool
otherwise = Table rh rh a -> Table rh rh a
forall a. a -> a
id
budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text (Maybe MixedAmount, Maybe MixedAmount)
budgetReportAsTable :: ReportOpts
-> BudgetReport -> Table AccountName AccountName BudgetCell
budgetReportAsTable
ropts :: ReportOpts
ropts@ReportOpts{BalanceType
balancetype_ :: BalanceType
balancetype_ :: ReportOpts -> BalanceType
balancetype_}
(PeriodicReport [DateSpan]
spans [PeriodicReportRow DisplayName BudgetCell]
rows (PeriodicReportRow ()
_ [BudgetCell]
coltots BudgetCell
grandtot BudgetCell
grandavg)) =
Table AccountName AccountName BudgetCell
-> Table AccountName AccountName BudgetCell
forall ch.
Table AccountName ch BudgetCell -> Table AccountName ch BudgetCell
addtotalrow (Table AccountName AccountName BudgetCell
-> Table AccountName AccountName BudgetCell)
-> Table AccountName AccountName BudgetCell
-> Table AccountName AccountName BudgetCell
forall a b. (a -> b) -> a -> b
$
Header AccountName
-> Header AccountName
-> [[BudgetCell]]
-> Table AccountName AccountName BudgetCell
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
Table
(Properties -> [Header AccountName] -> Header AccountName
forall h. Properties -> [Header h] -> Header h
T.Group Properties
NoLine ([Header AccountName] -> Header AccountName)
-> [Header AccountName] -> Header AccountName
forall a b. (a -> b) -> a -> b
$ (AccountName -> Header AccountName)
-> [AccountName] -> [Header AccountName]
forall a b. (a -> b) -> [a] -> [b]
map AccountName -> Header AccountName
forall h. h -> Header h
Header [AccountName]
accts)
(Properties -> [Header AccountName] -> Header AccountName
forall h. Properties -> [Header h] -> Header h
T.Group Properties
NoLine ([Header AccountName] -> Header AccountName)
-> [Header AccountName] -> Header AccountName
forall a b. (a -> b) -> a -> b
$ (AccountName -> Header AccountName)
-> [AccountName] -> [Header AccountName]
forall a b. (a -> b) -> [a] -> [b]
map AccountName -> Header AccountName
forall h. h -> Header h
Header [AccountName]
colheadings)
((PeriodicReportRow DisplayName BudgetCell -> [BudgetCell])
-> [PeriodicReportRow DisplayName BudgetCell] -> [[BudgetCell]]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName BudgetCell -> [BudgetCell]
forall a a. PeriodicReportRow a a -> [a]
rowvals [PeriodicReportRow DisplayName BudgetCell]
rows)
where
colheadings :: [AccountName]
colheadings = (DateSpan -> AccountName) -> [DateSpan] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map (BalanceType -> [DateSpan] -> DateSpan -> AccountName
reportPeriodName BalanceType
balancetype_ [DateSpan]
spans) [DateSpan]
spans
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ [AccountName
" Total" | ReportOpts -> Bool
row_total_ ReportOpts
ropts]
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ [AccountName
"Average" | ReportOpts -> Bool
average_ ReportOpts
ropts]
accts :: [AccountName]
accts = (PeriodicReportRow DisplayName BudgetCell -> AccountName)
-> [PeriodicReportRow DisplayName BudgetCell] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName BudgetCell -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
renderacct [PeriodicReportRow DisplayName BudgetCell]
rows
renderacct :: PeriodicReportRow DisplayName a -> AccountName
renderacct PeriodicReportRow DisplayName a
row = case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of
AccountListMode
ALTree -> Int -> AccountName -> AccountName
T.replicate ((PeriodicReportRow DisplayName a -> Int
forall a. PeriodicReportRow DisplayName a -> Int
prrDepth PeriodicReportRow DisplayName a
row Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2) AccountName
" " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> PeriodicReportRow DisplayName a -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrDisplayName PeriodicReportRow DisplayName a
row
AccountListMode
ALFlat -> Int -> AccountName -> AccountName
accountNameDrop (ReportOpts -> Int
drop_ ReportOpts
ropts) (AccountName -> AccountName) -> AccountName -> AccountName
forall a b. (a -> b) -> a -> b
$ PeriodicReportRow DisplayName a -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrFullName PeriodicReportRow DisplayName a
row
rowvals :: PeriodicReportRow a a -> [a]
rowvals (PeriodicReportRow a
_ [a]
as a
rowtot a
rowavg) =
[a]
as [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
rowtot | ReportOpts -> Bool
row_total_ ReportOpts
ropts] [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
rowavg | ReportOpts -> Bool
average_ ReportOpts
ropts]
addtotalrow :: Table AccountName ch BudgetCell -> Table AccountName ch BudgetCell
addtotalrow
| ReportOpts -> Bool
no_total_ ReportOpts
ropts = Table AccountName ch BudgetCell -> Table AccountName ch BudgetCell
forall a. a -> a
id
| Bool
otherwise = (Table AccountName ch BudgetCell
-> SemiTable AccountName BudgetCell
-> Table AccountName ch BudgetCell
forall rh ch a. Table rh ch a -> SemiTable rh a -> Table rh ch a
+----+ (AccountName -> [BudgetCell] -> SemiTable AccountName BudgetCell
forall rh a. rh -> [a] -> SemiTable rh a
row AccountName
"" ([BudgetCell] -> SemiTable AccountName BudgetCell)
-> [BudgetCell] -> SemiTable AccountName BudgetCell
forall a b. (a -> b) -> a -> b
$
[BudgetCell]
coltots [BudgetCell] -> [BudgetCell] -> [BudgetCell]
forall a. [a] -> [a] -> [a]
++ [BudgetCell
grandtot | ReportOpts -> Bool
row_total_ ReportOpts
ropts Bool -> Bool -> Bool
&& Bool -> Bool
not ([BudgetCell] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [BudgetCell]
coltots)]
[BudgetCell] -> [BudgetCell] -> [BudgetCell]
forall a. [a] -> [a] -> [a]
++ [BudgetCell
grandavg | ReportOpts -> Bool
average_ ReportOpts
ropts Bool -> Bool -> Bool
&& Bool -> Bool
not ([BudgetCell] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [BudgetCell]
coltots)]
))
reportPeriodName :: BalanceType -> [DateSpan] -> DateSpan -> T.Text
reportPeriodName :: BalanceType -> [DateSpan] -> DateSpan -> AccountName
reportPeriodName BalanceType
balancetype [DateSpan]
spans =
case BalanceType
balancetype of
BalanceType
PeriodChange -> if Bool
multiyear then DateSpan -> AccountName
showDateSpan else DateSpan -> AccountName
showDateSpanMonthAbbrev
where
multiyear :: Bool
multiyear = (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
1) (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ [Maybe Integer] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Maybe Integer] -> Int) -> [Maybe Integer] -> Int
forall a b. (a -> b) -> a -> b
$ [Maybe Integer] -> [Maybe Integer]
forall a. Ord a => [a] -> [a]
nubSort ([Maybe Integer] -> [Maybe Integer])
-> [Maybe Integer] -> [Maybe Integer]
forall a b. (a -> b) -> a -> b
$ (DateSpan -> Maybe Integer) -> [DateSpan] -> [Maybe Integer]
forall a b. (a -> b) -> [a] -> [b]
map DateSpan -> Maybe Integer
spanStartYear [DateSpan]
spans
BalanceType
_ -> AccountName -> (Day -> AccountName) -> Maybe Day -> AccountName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe AccountName
"" (Day -> AccountName
showDate (Day -> AccountName) -> (Day -> Day) -> Day -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Day
prevday) (Maybe Day -> AccountName)
-> (DateSpan -> Maybe Day) -> DateSpan -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateSpan -> Maybe Day
spanEnd
budgetReportAsCsv :: ReportOpts -> BudgetReport -> CSV
budgetReportAsCsv :: ReportOpts -> BudgetReport -> CSV
budgetReportAsCsv
ReportOpts{Bool
average_ :: Bool
average_ :: ReportOpts -> Bool
average_, Bool
row_total_ :: Bool
row_total_ :: ReportOpts -> Bool
row_total_, Bool
no_total_ :: Bool
no_total_ :: ReportOpts -> Bool
no_total_, Bool
transpose_ :: Bool
transpose_ :: ReportOpts -> Bool
transpose_}
(PeriodicReport [DateSpan]
colspans [PeriodicReportRow DisplayName BudgetCell]
items (PeriodicReportRow ()
_ [BudgetCell]
abtotals (Maybe MixedAmount
magrandtot,Maybe MixedAmount
mbgrandtot) (Maybe MixedAmount
magrandavg,Maybe MixedAmount
mbgrandavg)))
= (if Bool
transpose_ then CSV -> CSV
forall a. [[a]] -> [[a]]
transpose else CSV -> CSV
forall a. a -> a
id) (CSV -> CSV) -> CSV -> CSV
forall a b. (a -> b) -> a -> b
$
(AccountName
"Account" AccountName -> [AccountName] -> [AccountName]
forall a. a -> [a] -> [a]
:
(DateSpan -> [AccountName]) -> [DateSpan] -> [AccountName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\DateSpan
span -> [DateSpan -> AccountName
showDateSpan DateSpan
span, AccountName
"budget"]) [DateSpan]
colspans
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ CSV -> [AccountName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[AccountName
"Total" ,AccountName
"budget"] | Bool
row_total_]
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ CSV -> [AccountName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[AccountName
"Average",AccountName
"budget"] | Bool
average_]
) [AccountName] -> CSV -> CSV
forall a. a -> [a] -> [a]
:
[DisplayName -> AccountName
displayFull DisplayName
a AccountName -> [AccountName] -> [AccountName]
forall a. a -> [a] -> [a]
:
(Maybe MixedAmount -> AccountName)
-> [Maybe MixedAmount] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map Maybe MixedAmount -> AccountName
showmamt ([BudgetCell] -> [Maybe MixedAmount]
forall a. [(a, a)] -> [a]
flattentuples [BudgetCell]
abamts)
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ CSV -> [AccountName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
mactualrowtot, Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
mbudgetrowtot] | Bool
row_total_]
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ CSV -> [AccountName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
mactualrowavg, Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
mbudgetrowavg] | Bool
average_]
| PeriodicReportRow DisplayName
a [BudgetCell]
abamts (Maybe MixedAmount
mactualrowtot,Maybe MixedAmount
mbudgetrowtot) (Maybe MixedAmount
mactualrowavg,Maybe MixedAmount
mbudgetrowavg) <- [PeriodicReportRow DisplayName BudgetCell]
items
]
CSV -> CSV -> CSV
forall a. [a] -> [a] -> [a]
++ [CSV] -> CSV
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
[
AccountName
"Total:" AccountName -> [AccountName] -> [AccountName]
forall a. a -> [a] -> [a]
:
(Maybe MixedAmount -> AccountName)
-> [Maybe MixedAmount] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map Maybe MixedAmount -> AccountName
showmamt ([BudgetCell] -> [Maybe MixedAmount]
forall a. [(a, a)] -> [a]
flattentuples [BudgetCell]
abtotals)
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ CSV -> [AccountName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
magrandtot,Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
mbgrandtot] | Bool
row_total_]
[AccountName] -> [AccountName] -> [AccountName]
forall a. [a] -> [a] -> [a]
++ CSV -> [AccountName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
magrandavg,Maybe MixedAmount -> AccountName
showmamt Maybe MixedAmount
mbgrandavg] | Bool
average_]
]
| Bool -> Bool
not Bool
no_total_
]
where
flattentuples :: [(a, a)] -> [a]
flattentuples [(a, a)]
abs = [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[a
a,a
b] | (a
a,a
b) <- [(a, a)]
abs]
showmamt :: Maybe MixedAmount -> AccountName
showmamt = AccountName
-> (MixedAmount -> AccountName) -> Maybe MixedAmount -> AccountName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe AccountName
"" (WideBuilder -> AccountName
wbToText (WideBuilder -> AccountName)
-> (MixedAmount -> WideBuilder) -> MixedAmount -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
oneLine)
tests_BudgetReport :: TestTree
tests_BudgetReport = String -> [TestTree] -> TestTree
tests String
"BudgetReport" [
]