{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hledger.Reports.MultiBalanceReport (
MultiBalanceReport,
MultiBalanceReportRow,
multiBalanceReport,
multiBalanceReportWith,
compoundBalanceReport,
compoundBalanceReportWith,
sortRows,
sortRowsLike,
makeReportQuery,
getPostingsByColumn,
getPostings,
startingPostings,
generateMultiBalanceReport,
tests_MultiBalanceReport
)
where
import Control.Monad (guard)
import Data.Bifunctor (second)
import Data.Foldable (toList)
import Data.List (sortOn, transpose)
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, mapMaybe)
import Data.Ord (Down(..))
import Data.Semigroup (sconcat)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Time.Calendar (fromGregorian)
import Safe (lastDef, minimumMay)
import Hledger.Data
import Hledger.Query
import Hledger.Utils hiding (dbg3,dbg4,dbg5)
import qualified Hledger.Utils
import Hledger.Reports.ReportOptions
import Hledger.Reports.ReportTypes
dbg3 :: [Char] -> a -> a
dbg3 [Char]
s = let p :: [Char]
p = [Char]
"multiBalanceReport" in [Char] -> a -> a
forall a. Show a => [Char] -> a -> a
Hledger.Utils.dbg3 ([Char]
p[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
" "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
s)
dbg4 :: [Char] -> a -> a
dbg4 [Char]
s = let p :: [Char]
p = [Char]
"multiBalanceReport" in [Char] -> a -> a
forall a. Show a => [Char] -> a -> a
Hledger.Utils.dbg4 ([Char]
p[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
" "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
s)
dbg5 :: [Char] -> a -> a
dbg5 [Char]
s = let p :: [Char]
p = [Char]
"multiBalanceReport" in [Char] -> a -> a
forall a. Show a => [Char] -> a -> a
Hledger.Utils.dbg5 ([Char]
p[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
" "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
s)
type MultiBalanceReport = PeriodicReport DisplayName MixedAmount
type MultiBalanceReportRow = PeriodicReportRow DisplayName MixedAmount
type ClippedAccountName = AccountName
multiBalanceReport :: ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport :: ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport ReportSpec
rspec Journal
j = ReportSpec
-> Journal
-> PriceOracle
-> Set CommoditySymbol
-> MultiBalanceReport
multiBalanceReportWith ReportSpec
rspec Journal
j (Bool -> Journal -> PriceOracle
journalPriceOracle Bool
infer Journal
j) Set CommoditySymbol
forall a. Monoid a => a
mempty
where infer :: Bool
infer = ReportOpts -> Bool
infer_prices_ (ReportOpts -> Bool) -> ReportOpts -> Bool
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec
multiBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> Set AccountName -> MultiBalanceReport
multiBalanceReportWith :: ReportSpec
-> Journal
-> PriceOracle
-> Set CommoditySymbol
-> MultiBalanceReport
multiBalanceReportWith ReportSpec
rspec' Journal
j PriceOracle
priceoracle Set CommoditySymbol
unelidableaccts = MultiBalanceReport
report
where
(DateSpan
reportspan, [DateSpan]
colspans) = Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan Journal
j ReportSpec
rspec'
rspec :: ReportSpec
rspec = [Char] -> ReportSpec -> ReportSpec
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"reportopts" (ReportSpec -> ReportSpec) -> ReportSpec -> ReportSpec
forall a b. (a -> b) -> a -> b
$ ReportSpec -> DateSpan -> ReportSpec
makeReportQuery ReportSpec
rspec' DateSpan
reportspan
colps :: [(DateSpan, [Posting])]
colps = [Char] -> [(DateSpan, [Posting])] -> [(DateSpan, [Posting])]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"colps" ([(DateSpan, [Posting])] -> [(DateSpan, [Posting])])
-> [(DateSpan, [Posting])] -> [(DateSpan, [Posting])]
forall a b. (a -> b) -> a -> b
$ ReportSpec
-> Journal -> PriceOracle -> [DateSpan] -> [(DateSpan, [Posting])]
getPostingsByColumn ReportSpec
rspec Journal
j PriceOracle
priceoracle [DateSpan]
colspans
startbals :: HashMap CommoditySymbol Account
startbals = [Char]
-> HashMap CommoditySymbol Account
-> HashMap CommoditySymbol Account
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"startbals" (HashMap CommoditySymbol Account
-> HashMap CommoditySymbol Account)
-> HashMap CommoditySymbol Account
-> HashMap CommoditySymbol Account
forall a b. (a -> b) -> a -> b
$
ReportSpec
-> Journal
-> PriceOracle
-> [Posting]
-> HashMap CommoditySymbol Account
startingBalances ReportSpec
rspec Journal
j PriceOracle
priceoracle ([Posting] -> HashMap CommoditySymbol Account)
-> [Posting] -> HashMap CommoditySymbol Account
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PriceOracle -> DateSpan -> [Posting]
startingPostings ReportSpec
rspec Journal
j PriceOracle
priceoracle DateSpan
reportspan
report :: MultiBalanceReport
report = [Char] -> MultiBalanceReport -> MultiBalanceReport
forall a. Show a => [Char] -> a -> a
dbg4 [Char]
"multiBalanceReportWith" (MultiBalanceReport -> MultiBalanceReport)
-> MultiBalanceReport -> MultiBalanceReport
forall a b. (a -> b) -> a -> b
$
ReportSpec
-> Journal
-> PriceOracle
-> Set CommoditySymbol
-> [(DateSpan, [Posting])]
-> HashMap CommoditySymbol Account
-> MultiBalanceReport
generateMultiBalanceReport ReportSpec
rspec Journal
j PriceOracle
priceoracle Set CommoditySymbol
unelidableaccts [(DateSpan, [Posting])]
colps HashMap CommoditySymbol Account
startbals
compoundBalanceReport :: ReportSpec -> Journal -> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReport :: forall a.
ReportSpec
-> Journal
-> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReport ReportSpec
rspec Journal
j = ReportSpec
-> Journal
-> PriceOracle
-> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
forall a.
ReportSpec
-> Journal
-> PriceOracle
-> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReportWith ReportSpec
rspec Journal
j (Bool -> Journal -> PriceOracle
journalPriceOracle Bool
infer Journal
j)
where infer :: Bool
infer = ReportOpts -> Bool
infer_prices_ (ReportOpts -> Bool) -> ReportOpts -> Bool
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec
compoundBalanceReportWith :: ReportSpec -> Journal -> PriceOracle
-> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReportWith :: forall a.
ReportSpec
-> Journal
-> PriceOracle
-> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReportWith ReportSpec
rspec' Journal
j PriceOracle
priceoracle [CBCSubreportSpec a]
subreportspecs = CompoundPeriodicReport a MixedAmount
cbr
where
(DateSpan
reportspan, [DateSpan]
colspans) = Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan Journal
j ReportSpec
rspec'
rspec :: ReportSpec
rspec = [Char] -> ReportSpec -> ReportSpec
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"reportopts" (ReportSpec -> ReportSpec) -> ReportSpec -> ReportSpec
forall a b. (a -> b) -> a -> b
$ ReportSpec -> DateSpan -> ReportSpec
makeReportQuery ReportSpec
rspec' DateSpan
reportspan
colps :: [(DateSpan, [Posting])]
colps = [Char] -> [(DateSpan, [Posting])] -> [(DateSpan, [Posting])]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"colps" ([(DateSpan, [Posting])] -> [(DateSpan, [Posting])])
-> [(DateSpan, [Posting])] -> [(DateSpan, [Posting])]
forall a b. (a -> b) -> a -> b
$ ReportSpec
-> Journal -> PriceOracle -> [DateSpan] -> [(DateSpan, [Posting])]
getPostingsByColumn ReportSpec
rspec Journal
j PriceOracle
priceoracle [DateSpan]
colspans
startps :: [Posting]
startps = [Char] -> [Posting] -> [Posting]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"startps" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PriceOracle -> DateSpan -> [Posting]
startingPostings ReportSpec
rspec Journal
j PriceOracle
priceoracle DateSpan
reportspan
subreports :: [(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
subreports = (CBCSubreportSpec a
-> (CommoditySymbol, PeriodicReport a MixedAmount, Bool))
-> [CBCSubreportSpec a]
-> [(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
forall a b. (a -> b) -> [a] -> [b]
map CBCSubreportSpec a
-> (CommoditySymbol, PeriodicReport a MixedAmount, Bool)
forall {a}.
CBCSubreportSpec a
-> (CommoditySymbol, PeriodicReport a MixedAmount, Bool)
generateSubreport [CBCSubreportSpec a]
subreportspecs
where
generateSubreport :: CBCSubreportSpec a
-> (CommoditySymbol, PeriodicReport a MixedAmount, Bool)
generateSubreport CBCSubreportSpec{Bool
CommoditySymbol
Query
ReportOpts -> ReportOpts
MultiBalanceReport -> PeriodicReport a MixedAmount
cbcsubreporttitle :: CommoditySymbol
cbcsubreportquery :: Query
cbcsubreportoptions :: ReportOpts -> ReportOpts
cbcsubreporttransform :: MultiBalanceReport -> PeriodicReport a MixedAmount
cbcsubreportincreasestotal :: Bool
cbcsubreporttitle :: forall a. CBCSubreportSpec a -> CommoditySymbol
cbcsubreportquery :: forall a. CBCSubreportSpec a -> Query
cbcsubreportoptions :: forall a. CBCSubreportSpec a -> ReportOpts -> ReportOpts
cbcsubreporttransform :: forall a.
CBCSubreportSpec a
-> MultiBalanceReport -> PeriodicReport a MixedAmount
cbcsubreportincreasestotal :: forall a. CBCSubreportSpec a -> Bool
..} =
( CommoditySymbol
cbcsubreporttitle
, MultiBalanceReport -> PeriodicReport a MixedAmount
cbcsubreporttransform (MultiBalanceReport -> PeriodicReport a MixedAmount)
-> MultiBalanceReport -> PeriodicReport a MixedAmount
forall a b. (a -> b) -> a -> b
$
ReportSpec
-> Journal
-> PriceOracle
-> Set CommoditySymbol
-> [(DateSpan, [Posting])]
-> HashMap CommoditySymbol Account
-> MultiBalanceReport
generateMultiBalanceReport ReportSpec
rspecsub Journal
j PriceOracle
priceoracle Set CommoditySymbol
forall a. Monoid a => a
mempty [(DateSpan, [Posting])]
colps' HashMap CommoditySymbol Account
startbals'
, Bool
cbcsubreportincreasestotal
)
where
ropts :: ReportOpts
ropts = ReportOpts -> ReportOpts
cbcsubreportoptions (ReportOpts -> ReportOpts) -> ReportOpts -> ReportOpts
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec
rspecsub :: ReportSpec
rspecsub = ReportSpec
rspec{_rsReportOpts=ropts, _rsQuery=And [cbcsubreportquery, _rsQuery rspec]}
startbals' :: HashMap CommoditySymbol Account
startbals' = ReportSpec
-> Journal
-> PriceOracle
-> [Posting]
-> HashMap CommoditySymbol Account
startingBalances ReportSpec
rspecsub Journal
j PriceOracle
priceoracle ([Posting] -> HashMap CommoditySymbol Account)
-> [Posting] -> HashMap CommoditySymbol Account
forall a b. (a -> b) -> a -> b
$
(Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter ((CommoditySymbol -> Maybe AccountType) -> Query -> Posting -> Bool
matchesPostingExtra (Journal -> CommoditySymbol -> Maybe AccountType
journalAccountType Journal
j) Query
cbcsubreportquery) [Posting]
startps
colps' :: [(DateSpan, [Posting])]
colps' = ((DateSpan, [Posting]) -> (DateSpan, [Posting]))
-> [(DateSpan, [Posting])] -> [(DateSpan, [Posting])]
forall a b. (a -> b) -> [a] -> [b]
map (([Posting] -> [Posting])
-> (DateSpan, [Posting]) -> (DateSpan, [Posting])
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (([Posting] -> [Posting])
-> (DateSpan, [Posting]) -> (DateSpan, [Posting]))
-> ([Posting] -> [Posting])
-> (DateSpan, [Posting])
-> (DateSpan, [Posting])
forall a b. (a -> b) -> a -> b
$ (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter ((CommoditySymbol -> Maybe AccountType) -> Query -> Posting -> Bool
matchesPostingExtra (Journal -> CommoditySymbol -> Maybe AccountType
journalAccountType Journal
j) Query
cbcsubreportquery)) [(DateSpan, [Posting])]
colps
overalltotals :: PeriodicReportRow () MixedAmount
overalltotals = case [(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
subreports of
[] -> ()
-> [MixedAmount]
-> MixedAmount
-> MixedAmount
-> PeriodicReportRow () MixedAmount
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow () [] MixedAmount
nullmixedamt MixedAmount
nullmixedamt
((CommoditySymbol, PeriodicReport a MixedAmount, Bool)
r:[(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
rs) -> NonEmpty (PeriodicReportRow () MixedAmount)
-> PeriodicReportRow () MixedAmount
forall a. Semigroup a => NonEmpty a -> a
sconcat (NonEmpty (PeriodicReportRow () MixedAmount)
-> PeriodicReportRow () MixedAmount)
-> NonEmpty (PeriodicReportRow () MixedAmount)
-> PeriodicReportRow () MixedAmount
forall a b. (a -> b) -> a -> b
$ ((CommoditySymbol, PeriodicReport a MixedAmount, Bool)
-> PeriodicReportRow () MixedAmount)
-> NonEmpty (CommoditySymbol, PeriodicReport a MixedAmount, Bool)
-> NonEmpty (PeriodicReportRow () MixedAmount)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CommoditySymbol, PeriodicReport a MixedAmount, Bool)
-> PeriodicReportRow () MixedAmount
forall {a} {a}.
(a, PeriodicReport a MixedAmount, Bool)
-> PeriodicReportRow () MixedAmount
subreportTotal ((CommoditySymbol, PeriodicReport a MixedAmount, Bool)
r(CommoditySymbol, PeriodicReport a MixedAmount, Bool)
-> [(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
-> NonEmpty (CommoditySymbol, PeriodicReport a MixedAmount, Bool)
forall a. a -> [a] -> NonEmpty a
:|[(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
rs)
where
subreportTotal :: (a, PeriodicReport a MixedAmount, Bool)
-> PeriodicReportRow () MixedAmount
subreportTotal (a
_, PeriodicReport a MixedAmount
sr, Bool
increasestotal) =
(if Bool
increasestotal then PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount
forall a. a -> a
id else (MixedAmount -> MixedAmount)
-> PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount
forall a b.
(a -> b) -> PeriodicReportRow () a -> PeriodicReportRow () b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MixedAmount -> MixedAmount
maNegate) (PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount)
-> PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount
forall a b. (a -> b) -> a -> b
$ PeriodicReport a MixedAmount -> PeriodicReportRow () MixedAmount
forall a b. PeriodicReport a b -> PeriodicReportRow () b
prTotals PeriodicReport a MixedAmount
sr
cbr :: CompoundPeriodicReport a MixedAmount
cbr = CommoditySymbol
-> [DateSpan]
-> [(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
-> PeriodicReportRow () MixedAmount
-> CompoundPeriodicReport a MixedAmount
forall a b.
CommoditySymbol
-> [DateSpan]
-> [(CommoditySymbol, PeriodicReport a b, Bool)]
-> PeriodicReportRow () b
-> CompoundPeriodicReport a b
CompoundPeriodicReport CommoditySymbol
"" (((DateSpan, [Posting]) -> DateSpan)
-> [(DateSpan, [Posting])] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map (DateSpan, [Posting]) -> DateSpan
forall a b. (a, b) -> a
fst [(DateSpan, [Posting])]
colps) [(CommoditySymbol, PeriodicReport a MixedAmount, Bool)]
subreports PeriodicReportRow () MixedAmount
overalltotals
startingBalances :: ReportSpec -> Journal -> PriceOracle -> [Posting]
-> HashMap AccountName Account
startingBalances :: ReportSpec
-> Journal
-> PriceOracle
-> [Posting]
-> HashMap CommoditySymbol Account
startingBalances ReportSpec
rspec Journal
j PriceOracle
priceoracle [Posting]
ps =
Account -> DateSpan -> Map DateSpan Account -> Account
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault Account
nullacct DateSpan
emptydatespan
(Map DateSpan Account -> Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol Account
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReportSpec
-> Journal
-> PriceOracle
-> HashMap CommoditySymbol Account
-> [(DateSpan, [Posting])]
-> HashMap CommoditySymbol (Map DateSpan Account)
calculateReportMatrix ReportSpec
rspec Journal
j PriceOracle
priceoracle HashMap CommoditySymbol Account
forall a. Monoid a => a
mempty [(DateSpan
emptydatespan, [Posting]
ps)]
startingPostings :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> [Posting]
startingPostings :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> [Posting]
startingPostings rspec :: ReportSpec
rspec@ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
query,_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j PriceOracle
priceoracle DateSpan
reportspan =
ReportSpec -> Journal -> PriceOracle -> [Posting]
getPostings ReportSpec
rspec' Journal
j PriceOracle
priceoracle
where
rspec' :: ReportSpec
rspec' = ReportSpec
rspec{_rsQuery=startbalq,_rsReportOpts=ropts'}
ropts' :: ReportOpts
ropts' = case ReportOpts -> Maybe ValuationType
value_ ReportOpts
ropts of
Just (AtEnd Maybe CommoditySymbol
_) -> ReportOpts
ropts{period_=precedingperiod, value_=Nothing}
Maybe ValuationType
_ -> ReportOpts
ropts{period_=precedingperiod}
startbalq :: Query
startbalq = [Char] -> Query -> Query
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"startbalq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
datelessq, Query
precedingspanq]
datelessq :: Query
datelessq = [Char] -> Query -> Query
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"datelessq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDateOrDate2) Query
query
precedingperiod :: Period
precedingperiod = DateSpan -> Period
dateSpanAsPeriod (DateSpan -> Period) -> (Period -> DateSpan) -> Period -> Period
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateSpan -> DateSpan -> DateSpan
spanIntersect DateSpan
precedingspan (DateSpan -> DateSpan)
-> (Period -> DateSpan) -> Period -> DateSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Period -> DateSpan
periodAsDateSpan (Period -> Period) -> Period -> Period
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Period
period_ ReportOpts
ropts
precedingspan :: DateSpan
precedingspan = Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DateSpan -> Maybe Day
spanStart DateSpan
reportspan)
precedingspanq :: Query
precedingspanq = (if ReportOpts -> Bool
date2_ ReportOpts
ropts then DateSpan -> Query
Date2 else DateSpan -> Query
Date) (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ case DateSpan
precedingspan of
DateSpan Maybe EFDay
Nothing Maybe EFDay
Nothing -> DateSpan
emptydatespan
DateSpan
a -> DateSpan
a
makeReportQuery :: ReportSpec -> DateSpan -> ReportSpec
makeReportQuery :: ReportSpec -> DateSpan -> ReportSpec
makeReportQuery ReportSpec
rspec DateSpan
reportspan
| DateSpan
reportspan DateSpan -> DateSpan -> Bool
forall a. Eq a => a -> a -> Bool
== DateSpan
nulldatespan = ReportSpec
rspec
| Bool
otherwise = ReportSpec
rspec{_rsQuery=query}
where
query :: Query
query = Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query -> Query
dateless (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Query
_rsQuery ReportSpec
rspec, Query
reportspandatesq]
reportspandatesq :: Query
reportspandatesq = [Char] -> Query -> Query
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"reportspandatesq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ DateSpan -> Query
dateqcons DateSpan
reportspan
dateless :: Query -> Query
dateless = [Char] -> Query -> Query
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"dateless" (Query -> Query) -> (Query -> Query) -> Query -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDateOrDate2)
dateqcons :: DateSpan -> Query
dateqcons = if ReportOpts -> Bool
date2_ (ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec) then DateSpan -> Query
Date2 else DateSpan -> Query
Date
getPostingsByColumn :: ReportSpec -> Journal -> PriceOracle -> [DateSpan] -> [(DateSpan, [Posting])]
getPostingsByColumn :: ReportSpec
-> Journal -> PriceOracle -> [DateSpan] -> [(DateSpan, [Posting])]
getPostingsByColumn ReportSpec
rspec Journal
j PriceOracle
priceoracle [DateSpan]
colspans =
Bool
-> (Posting -> Day)
-> [DateSpan]
-> [Posting]
-> [(DateSpan, [Posting])]
forall a.
Bool -> (a -> Day) -> [DateSpan] -> [a] -> [(DateSpan, [a])]
groupByDateSpan Bool
True Posting -> Day
getDate [DateSpan]
colspans [Posting]
ps
where
ps :: [Posting]
ps = [Char] -> [Posting] -> [Posting]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"getPostingsByColumn" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PriceOracle -> [Posting]
getPostings ReportSpec
rspec Journal
j PriceOracle
priceoracle
getDate :: Posting -> Day
getDate = WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate (ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec))
getPostings :: ReportSpec -> Journal -> PriceOracle -> [Posting]
getPostings :: ReportSpec -> Journal -> PriceOracle -> [Posting]
getPostings rspec :: ReportSpec
rspec@ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
query, _rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j PriceOracle
priceoracle =
Journal -> [Posting]
journalPostings (Journal -> [Posting]) -> Journal -> [Posting]
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PriceOracle -> Journal
journalValueAndFilterPostingsWith ReportSpec
rspec' Journal
j PriceOracle
priceoracle
where
rspec' :: ReportSpec
rspec' = ReportSpec
rspec{_rsQuery=depthless, _rsReportOpts = ropts'}
ropts' :: ReportOpts
ropts' = if Maybe (Maybe CommoditySymbol) -> Bool
forall a. Maybe a -> Bool
isJust (ReportOpts -> Maybe (Maybe CommoditySymbol)
valuationAfterSum ReportOpts
ropts)
then ReportOpts
ropts{value_=Nothing, conversionop_=Just NoConversionOp}
else ReportOpts
ropts
depthless :: Query
depthless = [Char] -> Query -> Query
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"depthless" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDepth) Query
query
acctChanges :: ReportSpec -> Journal -> [Posting] -> HashMap ClippedAccountName Account
acctChanges :: ReportSpec
-> Journal -> [Posting] -> HashMap CommoditySymbol Account
acctChanges ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
query,_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts{AccountListMode
accountlistmode_ :: AccountListMode
accountlistmode_ :: ReportOpts -> AccountListMode
accountlistmode_, Bool
declared_ :: Bool
declared_ :: ReportOpts -> Bool
declared_}} Journal
j [Posting]
ps =
[(CommoditySymbol, Account)] -> HashMap CommoditySymbol Account
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList [(Account -> CommoditySymbol
aname Account
a, Account
a) | Account
a <- [Account]
accts]
where
ps' :: [Posting]
ps' = [Posting]
ps [Posting] -> [Posting] -> [Posting]
forall a. [a] -> [a] -> [a]
++ if Bool
declared_ then [Posting]
declaredacctps else []
where
declaredacctps :: [Posting]
declaredacctps =
[Posting
nullposting{paccount=a}
| CommoditySymbol
a <- Journal -> [CommoditySymbol]
journalLeafAccountNamesDeclared Journal
j
, (CommoditySymbol -> Maybe AccountType)
-> (CommoditySymbol -> [Tag]) -> Query -> CommoditySymbol -> Bool
matchesAccountExtra (Journal -> CommoditySymbol -> Maybe AccountType
journalAccountType Journal
j) (Journal -> CommoditySymbol -> [Tag]
journalAccountTags Journal
j) Query
accttypetagsq CommoditySymbol
a
]
where
accttypetagsq :: Query
accttypetagsq = [Char] -> Query -> Query
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"accttypetagsq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$
(Query -> Bool) -> Query -> Query
filterQueryOrNotQuery (\Query
q -> Query -> Bool
queryIsAcct Query
q Bool -> Bool -> Bool
|| Query -> Bool
queryIsType Query
q Bool -> Bool -> Bool
|| Query -> Bool
queryIsTag Query
q) Query
query
filterbydepth :: [Account] -> [Account]
filterbydepth = case AccountListMode
accountlistmode_ of
AccountListMode
ALTree -> (Account -> Bool) -> [Account] -> [Account]
forall a. (a -> Bool) -> [a] -> [a]
filter (CommoditySymbol -> Bool
depthMatches (CommoditySymbol -> Bool)
-> (Account -> CommoditySymbol) -> Account -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Account -> CommoditySymbol
aname)
AccountListMode
ALFlat -> DepthSpec -> [Account] -> [Account]
clipAccountsAndAggregate DepthSpec
depthSpec
([Account] -> [Account])
-> ([Account] -> [Account]) -> [Account] -> [Account]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Account -> Bool) -> [Account] -> [Account]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<) (Int -> Bool) -> (Account -> Int) -> Account -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Account -> Int
anumpostings)
where
depthSpec :: DepthSpec
depthSpec = [Char] -> DepthSpec -> DepthSpec
forall a. Show a => [Char] -> a -> a
dbg3 [Char]
"depthq" (DepthSpec -> DepthSpec)
-> (Query -> DepthSpec) -> Query -> DepthSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> DepthSpec
queryDepth (Query -> DepthSpec) -> Query -> DepthSpec
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDepth Query
query
depthMatches :: CommoditySymbol -> Bool
depthMatches CommoditySymbol
name = Bool -> (Int -> Bool) -> Maybe Int -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (CommoditySymbol -> Int
accountNameLevel CommoditySymbol
name Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=) (Maybe Int -> Bool) -> Maybe Int -> Bool
forall a b. (a -> b) -> a -> b
$ DepthSpec -> CommoditySymbol -> Maybe Int
getAccountNameClippedDepth DepthSpec
depthSpec CommoditySymbol
name
accts :: [Account]
accts = [Account] -> [Account]
filterbydepth ([Account] -> [Account]) -> [Account] -> [Account]
forall a b. (a -> b) -> a -> b
$ Int -> [Account] -> [Account]
forall a. Int -> [a] -> [a]
drop Int
1 ([Account] -> [Account]) -> [Account] -> [Account]
forall a b. (a -> b) -> a -> b
$ [Posting] -> [Account]
accountsFromPostings [Posting]
ps'
calculateReportMatrix :: ReportSpec -> Journal -> PriceOracle
-> HashMap ClippedAccountName Account
-> [(DateSpan, [Posting])]
-> HashMap ClippedAccountName (Map DateSpan Account)
calculateReportMatrix :: ReportSpec
-> Journal
-> PriceOracle
-> HashMap CommoditySymbol Account
-> [(DateSpan, [Posting])]
-> HashMap CommoditySymbol (Map DateSpan Account)
calculateReportMatrix rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j PriceOracle
priceoracle HashMap CommoditySymbol Account
startbals [(DateSpan, [Posting])]
colps =
(CommoditySymbol -> Map DateSpan Account -> Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall k v1 v2. (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.mapWithKey CommoditySymbol -> Map DateSpan Account -> Map DateSpan Account
rowbals HashMap CommoditySymbol (Map DateSpan Account)
allchanges
where
rowbals :: CommoditySymbol -> Map DateSpan Account -> Map DateSpan Account
rowbals CommoditySymbol
name Map DateSpan Account
unvaluedChanges = [Char] -> Map DateSpan Account -> Map DateSpan Account
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"rowbals" (Map DateSpan Account -> Map DateSpan Account)
-> Map DateSpan Account -> Map DateSpan Account
forall a b. (a -> b) -> a -> b
$ case ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts of
BalanceAccumulation
PerPeriod -> Map DateSpan Account
changes
BalanceAccumulation
Cumulative -> Map DateSpan Account
cumulative
BalanceAccumulation
Historical -> Map DateSpan Account
historical
where
changes :: Map DateSpan Account
changes = case ReportOpts -> BalanceCalculation
balancecalc_ ReportOpts
ropts of
BalanceCalculation
CalcChange -> (DateSpan -> Account -> Account)
-> Map DateSpan Account -> Map DateSpan Account
forall k a b. (k -> a -> b) -> Map k a -> Map k b
M.mapWithKey DateSpan -> Account -> Account
avalue Map DateSpan Account
unvaluedChanges
BalanceCalculation
CalcBudget -> (DateSpan -> Account -> Account)
-> Map DateSpan Account -> Map DateSpan Account
forall k a b. (k -> a -> b) -> Map k a -> Map k b
M.mapWithKey DateSpan -> Account -> Account
avalue Map DateSpan Account
unvaluedChanges
BalanceCalculation
CalcValueChange -> Account -> Map DateSpan Account -> Map DateSpan Account
forall k. Account -> Map k Account -> Map k Account
periodChanges Account
valuedStart Map DateSpan Account
historical
BalanceCalculation
CalcGain -> Account -> Map DateSpan Account -> Map DateSpan Account
forall k. Account -> Map k Account -> Map k Account
periodChanges Account
valuedStart Map DateSpan Account
historical
BalanceCalculation
CalcPostingsCount -> (DateSpan -> Account -> Account)
-> Map DateSpan Account -> Map DateSpan Account
forall k a b. (k -> a -> b) -> Map k a -> Map k b
M.mapWithKey DateSpan -> Account -> Account
avalue Map DateSpan Account
unvaluedChanges
historical :: Map DateSpan Account
historical = (DateSpan -> Account -> Account)
-> Map DateSpan Account -> Map DateSpan Account
forall k a b. (k -> a -> b) -> Map k a -> Map k b
M.mapWithKey DateSpan -> Account -> Account
avalue (Map DateSpan Account -> Map DateSpan Account)
-> Map DateSpan Account -> Map DateSpan Account
forall a b. (a -> b) -> a -> b
$ Account -> Map DateSpan Account -> Map DateSpan Account
cumulativeSum Account
startingBalance Map DateSpan Account
unvaluedChanges
cumulative :: Map DateSpan Account
cumulative = Account -> Map DateSpan Account -> Map DateSpan Account
cumulativeSum Account
nullacct Map DateSpan Account
changes
startingBalance :: Account
startingBalance = Account
-> CommoditySymbol -> HashMap CommoditySymbol Account -> Account
forall k v. (Eq k, Hashable k) => v -> k -> HashMap k v -> v
HM.lookupDefault Account
nullacct CommoditySymbol
name HashMap CommoditySymbol Account
startbals
valuedStart :: Account
valuedStart = DateSpan -> Account -> Account
avalue (Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
historicalDate)) Account
startingBalance
colacctchanges :: [(DateSpan, HashMap CommoditySymbol Account)]
colacctchanges = [Char]
-> [(DateSpan, HashMap CommoditySymbol Account)]
-> [(DateSpan, HashMap CommoditySymbol Account)]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"colacctchanges" ([(DateSpan, HashMap CommoditySymbol Account)]
-> [(DateSpan, HashMap CommoditySymbol Account)])
-> [(DateSpan, HashMap CommoditySymbol Account)]
-> [(DateSpan, HashMap CommoditySymbol Account)]
forall a b. (a -> b) -> a -> b
$ ((DateSpan, [Posting])
-> (DateSpan, HashMap CommoditySymbol Account))
-> [(DateSpan, [Posting])]
-> [(DateSpan, HashMap CommoditySymbol Account)]
forall a b. (a -> b) -> [a] -> [b]
map (([Posting] -> HashMap CommoditySymbol Account)
-> (DateSpan, [Posting])
-> (DateSpan, HashMap CommoditySymbol Account)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (([Posting] -> HashMap CommoditySymbol Account)
-> (DateSpan, [Posting])
-> (DateSpan, HashMap CommoditySymbol Account))
-> ([Posting] -> HashMap CommoditySymbol Account)
-> (DateSpan, [Posting])
-> (DateSpan, HashMap CommoditySymbol Account)
forall a b. (a -> b) -> a -> b
$ ReportSpec
-> Journal -> [Posting] -> HashMap CommoditySymbol Account
acctChanges ReportSpec
rspec Journal
j) [(DateSpan, [Posting])]
colps :: [(DateSpan, HashMap ClippedAccountName Account)]
acctchanges :: HashMap CommoditySymbol (Map DateSpan Account)
acctchanges = [Char]
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"acctchanges" (HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account))
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall a b. (a -> b) -> a -> b
$ [(DateSpan, HashMap CommoditySymbol Account)]
-> HashMap CommoditySymbol (Map DateSpan Account)
forall a.
[(DateSpan, HashMap CommoditySymbol a)]
-> HashMap CommoditySymbol (Map DateSpan a)
transposeMap [(DateSpan, HashMap CommoditySymbol Account)]
colacctchanges :: HashMap AccountName (Map DateSpan Account)
allchanges :: HashMap CommoditySymbol (Map DateSpan Account)
allchanges = ((Map DateSpan Account
-> Map DateSpan Account -> Map DateSpan Account
forall a. Semigroup a => a -> a -> a
<>Map DateSpan Account
zeros) (Map DateSpan Account -> Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap CommoditySymbol (Map DateSpan Account)
acctchanges) HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall a. Semigroup a => a -> a -> a
<> (Map DateSpan Account
zeros Map DateSpan Account
-> HashMap CommoditySymbol Account
-> HashMap CommoditySymbol (Map DateSpan Account)
forall a b.
a -> HashMap CommoditySymbol b -> HashMap CommoditySymbol a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ HashMap CommoditySymbol Account
startbals)
avalue :: DateSpan -> Account -> Account
avalue = (MixedAmount -> MixedAmount) -> Account -> Account
acctApplyBoth ((MixedAmount -> MixedAmount) -> Account -> Account)
-> (DateSpan -> MixedAmount -> MixedAmount)
-> DateSpan
-> Account
-> Account
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts
-> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount
mixedAmountApplyValuationAfterSumFromOptsWith ReportOpts
ropts Journal
j PriceOracle
priceoracle
acctApplyBoth :: (MixedAmount -> MixedAmount) -> Account -> Account
acctApplyBoth MixedAmount -> MixedAmount
f Account
a = Account
a{aibalance = f $ aibalance a, aebalance = f $ aebalance a}
historicalDate :: Maybe Day
historicalDate = [Day] -> Maybe Day
forall a. Ord a => [a] -> Maybe a
minimumMay ([Day] -> Maybe Day) -> [Day] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ (DateSpan -> Maybe Day) -> [DateSpan] -> [Day]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DateSpan -> Maybe Day
spanStart [DateSpan]
colspans
zeros :: Map DateSpan Account
zeros = [(DateSpan, Account)] -> Map DateSpan Account
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(DateSpan
spn, Account
nullacct) | DateSpan
spn <- [DateSpan]
colspans]
colspans :: [DateSpan]
colspans = ((DateSpan, [Posting]) -> DateSpan)
-> [(DateSpan, [Posting])] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map (DateSpan, [Posting]) -> DateSpan
forall a b. (a, b) -> a
fst [(DateSpan, [Posting])]
colps
generateMultiBalanceReport :: ReportSpec -> Journal -> PriceOracle -> Set AccountName
-> [(DateSpan, [Posting])] -> HashMap AccountName Account
-> MultiBalanceReport
generateMultiBalanceReport :: ReportSpec
-> Journal
-> PriceOracle
-> Set CommoditySymbol
-> [(DateSpan, [Posting])]
-> HashMap CommoditySymbol Account
-> MultiBalanceReport
generateMultiBalanceReport rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j PriceOracle
priceoracle Set CommoditySymbol
unelidableaccts [(DateSpan, [Posting])]
colps0 HashMap CommoditySymbol Account
startbals =
MultiBalanceReport
report
where
colps :: [(DateSpan, [Posting])]
colps =
if ReportOpts -> BalanceCalculation
balancecalc_ ReportOpts
ropts BalanceCalculation -> BalanceCalculation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceCalculation
CalcPostingsCount
then ((DateSpan, [Posting]) -> (DateSpan, [Posting]))
-> [(DateSpan, [Posting])] -> [(DateSpan, [Posting])]
forall a b. (a -> b) -> [a] -> [b]
map (([Posting] -> [Posting])
-> (DateSpan, [Posting]) -> (DateSpan, [Posting])
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ((Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map ((MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (MixedAmount -> MixedAmount -> MixedAmount
forall a b. a -> b -> a
const (MixedAmount -> MixedAmount -> MixedAmount)
-> MixedAmount -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ [Amount] -> MixedAmount
forall (t :: * -> *). Foldable t => t Amount -> MixedAmount
mixed [Quantity -> Amount
num Quantity
1])))) [(DateSpan, [Posting])]
colps0
else [(DateSpan, [Posting])]
colps0
matrix :: HashMap CommoditySymbol (Map DateSpan Account)
matrix = ReportSpec
-> Journal
-> PriceOracle
-> HashMap CommoditySymbol Account
-> [(DateSpan, [Posting])]
-> HashMap CommoditySymbol (Map DateSpan Account)
calculateReportMatrix ReportSpec
rspec Journal
j PriceOracle
priceoracle HashMap CommoditySymbol Account
startbals [(DateSpan, [Posting])]
colps
displaynames :: HashMap CommoditySymbol DisplayName
displaynames = [Char]
-> HashMap CommoditySymbol DisplayName
-> HashMap CommoditySymbol DisplayName
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"displaynames" (HashMap CommoditySymbol DisplayName
-> HashMap CommoditySymbol DisplayName)
-> HashMap CommoditySymbol DisplayName
-> HashMap CommoditySymbol DisplayName
forall a b. (a -> b) -> a -> b
$ ReportSpec
-> Set CommoditySymbol
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol DisplayName
displayedAccounts ReportSpec
rspec Set CommoditySymbol
unelidableaccts HashMap CommoditySymbol (Map DateSpan Account)
matrix
rows :: [PeriodicReportRow DisplayName MixedAmount]
rows = [Char]
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"rows" ([PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount])
-> ([PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount])
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if ReportOpts -> Bool
invert_ ReportOpts
ropts then (PeriodicReportRow DisplayName MixedAmount
-> PeriodicReportRow DisplayName MixedAmount)
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map ((MixedAmount -> MixedAmount)
-> PeriodicReportRow DisplayName MixedAmount
-> PeriodicReportRow DisplayName MixedAmount
forall a b.
(a -> b)
-> PeriodicReportRow DisplayName a
-> PeriodicReportRow DisplayName b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MixedAmount -> MixedAmount
maNegate) else [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a. a -> a
id)
([PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount])
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a b. (a -> b) -> a -> b
$ ReportOpts
-> HashMap CommoditySymbol DisplayName
-> HashMap CommoditySymbol (Map DateSpan Account)
-> [PeriodicReportRow DisplayName MixedAmount]
buildReportRows ReportOpts
ropts HashMap CommoditySymbol DisplayName
displaynames HashMap CommoditySymbol (Map DateSpan Account)
matrix
totalsrow :: PeriodicReportRow () MixedAmount
totalsrow = [Char]
-> PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"totalsrow" (PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount)
-> PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount
forall a b. (a -> b) -> a -> b
$ ReportOpts
-> [PeriodicReportRow DisplayName MixedAmount]
-> Int
-> PeriodicReportRow () MixedAmount
calculateTotalsRow ReportOpts
ropts [PeriodicReportRow DisplayName MixedAmount]
rows (Int -> PeriodicReportRow () MixedAmount)
-> Int -> PeriodicReportRow () MixedAmount
forall a b. (a -> b) -> a -> b
$ [(DateSpan, [Posting])] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(DateSpan, [Posting])]
colps
sortedrows :: [PeriodicReportRow DisplayName MixedAmount]
sortedrows = [Char]
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"sortedrows" ([PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount])
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a b. (a -> b) -> a -> b
$ ReportOpts
-> Journal
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortRows ReportOpts
ropts Journal
j [PeriodicReportRow DisplayName MixedAmount]
rows
report :: MultiBalanceReport
report = ReportOpts -> MultiBalanceReport -> MultiBalanceReport
reportPercent ReportOpts
ropts (MultiBalanceReport -> MultiBalanceReport)
-> MultiBalanceReport -> MultiBalanceReport
forall a b. (a -> b) -> a -> b
$ [DateSpan]
-> [PeriodicReportRow DisplayName MixedAmount]
-> PeriodicReportRow () MixedAmount
-> MultiBalanceReport
forall a b.
[DateSpan]
-> [PeriodicReportRow a b]
-> PeriodicReportRow () b
-> PeriodicReport a b
PeriodicReport (((DateSpan, [Posting]) -> DateSpan)
-> [(DateSpan, [Posting])] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map (DateSpan, [Posting]) -> DateSpan
forall a b. (a, b) -> a
fst [(DateSpan, [Posting])]
colps) [PeriodicReportRow DisplayName MixedAmount]
sortedrows PeriodicReportRow () MixedAmount
totalsrow
buildReportRows :: ReportOpts
-> HashMap AccountName DisplayName
-> HashMap AccountName (Map DateSpan Account)
-> [MultiBalanceReportRow]
buildReportRows :: ReportOpts
-> HashMap CommoditySymbol DisplayName
-> HashMap CommoditySymbol (Map DateSpan Account)
-> [PeriodicReportRow DisplayName MixedAmount]
buildReportRows ReportOpts
ropts HashMap CommoditySymbol DisplayName
displaynames =
HashMap CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
-> [PeriodicReportRow DisplayName MixedAmount]
forall a. HashMap CommoditySymbol a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
-> [PeriodicReportRow DisplayName MixedAmount])
-> (HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount))
-> HashMap CommoditySymbol (Map DateSpan Account)
-> [PeriodicReportRow DisplayName MixedAmount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommoditySymbol
-> Map DateSpan Account
-> Maybe (PeriodicReportRow DisplayName MixedAmount))
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
forall k v1 v2.
(k -> v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
HM.mapMaybeWithKey CommoditySymbol
-> Map DateSpan Account
-> Maybe (PeriodicReportRow DisplayName MixedAmount)
forall {t :: * -> *}.
Foldable t =>
CommoditySymbol
-> t Account -> Maybe (PeriodicReportRow DisplayName MixedAmount)
mkRow
where
mkRow :: CommoditySymbol
-> t Account -> Maybe (PeriodicReportRow DisplayName MixedAmount)
mkRow CommoditySymbol
name t Account
accts = do
DisplayName
displayname <- CommoditySymbol
-> HashMap CommoditySymbol DisplayName -> Maybe DisplayName
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup CommoditySymbol
name HashMap CommoditySymbol DisplayName
displaynames
PeriodicReportRow DisplayName MixedAmount
-> Maybe (PeriodicReportRow DisplayName MixedAmount)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (PeriodicReportRow DisplayName MixedAmount
-> Maybe (PeriodicReportRow DisplayName MixedAmount))
-> PeriodicReportRow DisplayName MixedAmount
-> Maybe (PeriodicReportRow DisplayName MixedAmount)
forall a b. (a -> b) -> a -> b
$ DisplayName
-> [MixedAmount]
-> MixedAmount
-> MixedAmount
-> PeriodicReportRow DisplayName MixedAmount
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow DisplayName
displayname [MixedAmount]
rowbals MixedAmount
rowtot MixedAmount
rowavg
where
rowbals :: [MixedAmount]
rowbals = (Account -> MixedAmount) -> [Account] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Account -> MixedAmount
balance ([Account] -> [MixedAmount]) -> [Account] -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$ t Account -> [Account]
forall a. t a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList t Account
accts
rowtot :: MixedAmount
rowtot = case ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts of
BalanceAccumulation
PerPeriod -> [MixedAmount] -> MixedAmount
forall (t :: * -> *). Foldable t => t MixedAmount -> MixedAmount
maSum [MixedAmount]
rowbals
BalanceAccumulation
_ -> MixedAmount -> [MixedAmount] -> MixedAmount
forall a. a -> [a] -> a
lastDef MixedAmount
nullmixedamt [MixedAmount]
rowbals
rowavg :: MixedAmount
rowavg = [MixedAmount] -> MixedAmount
averageMixedAmounts [MixedAmount]
rowbals
balance :: Account -> MixedAmount
balance = case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of AccountListMode
ALTree -> Account -> MixedAmount
aibalance; AccountListMode
ALFlat -> Account -> MixedAmount
aebalance
displayedAccounts :: ReportSpec
-> Set AccountName
-> HashMap AccountName (Map DateSpan Account)
-> HashMap AccountName DisplayName
displayedAccounts :: ReportSpec
-> Set CommoditySymbol
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol DisplayName
displayedAccounts ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
query,_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Set CommoditySymbol
unelidableaccts HashMap CommoditySymbol (Map DateSpan Account)
valuedaccts
| Bool
qdepthIsZero = CommoditySymbol
-> DisplayName -> HashMap CommoditySymbol DisplayName
forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton CommoditySymbol
"..." (DisplayName -> HashMap CommoditySymbol DisplayName)
-> DisplayName -> HashMap CommoditySymbol DisplayName
forall a b. (a -> b) -> a -> b
$ CommoditySymbol -> CommoditySymbol -> Int -> DisplayName
DisplayName CommoditySymbol
"..." CommoditySymbol
"..." Int
0
| Bool
otherwise = (CommoditySymbol -> Map DateSpan Account -> DisplayName)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol DisplayName
forall k v1 v2. (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.mapWithKey (\CommoditySymbol
a Map DateSpan Account
_ -> CommoditySymbol -> DisplayName
displayedName CommoditySymbol
a) HashMap CommoditySymbol (Map DateSpan Account)
displayedAccts
where
displayedName :: CommoditySymbol -> DisplayName
displayedName CommoditySymbol
name = case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of
AccountListMode
ALTree -> CommoditySymbol -> CommoditySymbol -> Int -> DisplayName
DisplayName CommoditySymbol
name CommoditySymbol
leaf (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
boringParents)
AccountListMode
ALFlat -> CommoditySymbol -> CommoditySymbol -> Int -> DisplayName
DisplayName CommoditySymbol
name CommoditySymbol
droppedName Int
0
where
droppedName :: CommoditySymbol
droppedName = Int -> CommoditySymbol -> CommoditySymbol
accountNameDrop (ReportOpts -> Int
drop_ ReportOpts
ropts) CommoditySymbol
name
leaf :: CommoditySymbol
leaf = [CommoditySymbol] -> CommoditySymbol
accountNameFromComponents ([CommoditySymbol] -> CommoditySymbol)
-> ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol]
-> CommoditySymbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CommoditySymbol] -> [CommoditySymbol]
forall a. [a] -> [a]
reverse ([CommoditySymbol] -> [CommoditySymbol])
-> ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol]
-> [CommoditySymbol]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommoditySymbol -> CommoditySymbol)
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map CommoditySymbol -> CommoditySymbol
accountLeafName ([CommoditySymbol] -> CommoditySymbol)
-> [CommoditySymbol] -> CommoditySymbol
forall a b. (a -> b) -> a -> b
$
CommoditySymbol
droppedName CommoditySymbol -> [CommoditySymbol] -> [CommoditySymbol]
forall a. a -> [a] -> [a]
: (CommoditySymbol -> Bool) -> [CommoditySymbol] -> [CommoditySymbol]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile CommoditySymbol -> Bool
notDisplayed [CommoditySymbol]
parents
level :: Int
level = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ (CommoditySymbol -> Int
accountNameLevel CommoditySymbol
name) Int -> Int -> Int
forall a. Num a => a -> a -> a
- ReportOpts -> Int
drop_ ReportOpts
ropts
parents :: [CommoditySymbol]
parents = Int -> [CommoditySymbol] -> [CommoditySymbol]
forall a. Int -> [a] -> [a]
take (Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ CommoditySymbol -> [CommoditySymbol]
parentAccountNames CommoditySymbol
name
boringParents :: Int
boringParents = if ReportOpts -> Bool
no_elide_ ReportOpts
ropts then Int
0 else [CommoditySymbol] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([CommoditySymbol] -> Int) -> [CommoditySymbol] -> Int
forall a b. (a -> b) -> a -> b
$ (CommoditySymbol -> Bool) -> [CommoditySymbol] -> [CommoditySymbol]
forall a. (a -> Bool) -> [a] -> [a]
filter CommoditySymbol -> Bool
notDisplayed [CommoditySymbol]
parents
notDisplayed :: CommoditySymbol -> Bool
notDisplayed = Bool -> Bool
not (Bool -> Bool)
-> (CommoditySymbol -> Bool) -> CommoditySymbol -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommoditySymbol
-> HashMap CommoditySymbol (Map DateSpan Account) -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`HM.member` HashMap CommoditySymbol (Map DateSpan Account)
displayedAccts)
displayedAccts :: HashMap CommoditySymbol (Map DateSpan Account)
displayedAccts = (if Bool
qdepthIsZero then HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall a. a -> a
id else (CommoditySymbol -> Map DateSpan Account -> Bool)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
HM.filterWithKey CommoditySymbol -> Map DateSpan Account -> Bool
forall {t :: * -> *}.
Foldable t =>
CommoditySymbol -> t Account -> Bool
keep) HashMap CommoditySymbol (Map DateSpan Account)
valuedaccts
where
keep :: CommoditySymbol -> t Account -> Bool
keep CommoditySymbol
name t Account
amts = CommoditySymbol -> t Account -> Bool
forall {t :: * -> *}.
Foldable t =>
CommoditySymbol -> t Account -> Bool
isInteresting CommoditySymbol
name t Account
amts Bool -> Bool -> Bool
|| CommoditySymbol
name CommoditySymbol -> HashMap CommoditySymbol Int -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`HM.member` HashMap CommoditySymbol Int
interestingParents
isInteresting :: CommoditySymbol -> t Account -> Bool
isInteresting CommoditySymbol
name t Account
amts =
Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
qdepth
Bool -> Bool -> Bool
&& ( CommoditySymbol
name CommoditySymbol -> Set CommoditySymbol -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set CommoditySymbol
unelidableaccts
Bool -> Bool -> Bool
||(ReportOpts -> Bool
empty_ ReportOpts
ropts Bool -> Bool -> Bool
&& t Account -> Bool
keepWhenEmpty t Account
amts)
Bool -> Bool -> Bool
|| Bool -> Bool
not ((Account -> MixedAmount) -> t Account -> Bool
forall {t :: * -> *} {a}.
Foldable t =>
(a -> MixedAmount) -> t a -> Bool
isZeroRow Account -> MixedAmount
balance t Account
amts)
)
where
d :: Int
d = CommoditySymbol -> Int
accountNameLevel CommoditySymbol
name
qdepth :: Int
qdepth = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
forall a. Bounded a => a
maxBound (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ DepthSpec -> CommoditySymbol -> Maybe Int
getAccountNameClippedDepth DepthSpec
depthspec CommoditySymbol
name
keepWhenEmpty :: t Account -> Bool
keepWhenEmpty = case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of
AccountListMode
ALFlat -> Bool -> t Account -> Bool
forall a b. a -> b -> a
const Bool
True
AccountListMode
ALTree -> (Account -> Bool) -> t Account -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ([Account] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Account] -> Bool) -> (Account -> [Account]) -> Account -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Account -> [Account]
asubs)
balance :: Account -> MixedAmount
balance = MixedAmount -> MixedAmount
maybeStripPrices (MixedAmount -> MixedAmount)
-> (Account -> MixedAmount) -> Account -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of
AccountListMode
ALTree | Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
qdepth -> Account -> MixedAmount
aibalance
AccountListMode
_ -> Account -> MixedAmount
aebalance
where maybeStripPrices :: MixedAmount -> MixedAmount
maybeStripPrices = if ReportOpts -> Maybe ConversionOp
conversionop_ ReportOpts
ropts Maybe ConversionOp -> Maybe ConversionOp -> Bool
forall a. Eq a => a -> a -> Bool
== ConversionOp -> Maybe ConversionOp
forall a. a -> Maybe a
Just ConversionOp
NoConversionOp then MixedAmount -> MixedAmount
forall a. a -> a
id else MixedAmount -> MixedAmount
mixedAmountStripCosts
interestingParents :: HashMap CommoditySymbol Int
interestingParents = [Char]
-> HashMap CommoditySymbol Int -> HashMap CommoditySymbol Int
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"interestingParents" (HashMap CommoditySymbol Int -> HashMap CommoditySymbol Int)
-> HashMap CommoditySymbol Int -> HashMap CommoditySymbol Int
forall a b. (a -> b) -> a -> b
$ case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of
AccountListMode
ALTree -> (CommoditySymbol -> Int -> Bool)
-> HashMap CommoditySymbol Int -> HashMap CommoditySymbol Int
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
HM.filterWithKey CommoditySymbol -> Int -> Bool
hasEnoughSubs HashMap CommoditySymbol Int
numSubs
AccountListMode
ALFlat -> HashMap CommoditySymbol Int
forall a. Monoid a => a
mempty
where
hasEnoughSubs :: CommoditySymbol -> Int -> Bool
hasEnoughSubs CommoditySymbol
name Int
nsubs = Int
nsubs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
minSubs Bool -> Bool -> Bool
&& CommoditySymbol -> Int
accountNameLevel CommoditySymbol
name Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> ReportOpts -> Int
drop_ ReportOpts
ropts
minSubs :: Int
minSubs = if ReportOpts -> Bool
no_elide_ ReportOpts
ropts then Int
1 else Int
2
isZeroRow :: (a -> MixedAmount) -> t a -> Bool
isZeroRow a -> MixedAmount
balance = (a -> Bool) -> t a -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (MixedAmount -> Bool
mixedAmountLooksZero (MixedAmount -> Bool) -> (a -> MixedAmount) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> MixedAmount
balance)
depthspec :: DepthSpec
depthspec = Query -> DepthSpec
queryDepth Query
query
qdepthIsZero :: Bool
qdepthIsZero = DepthSpec
depthspec DepthSpec -> DepthSpec -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe Int -> [(Regexp, Int)] -> DepthSpec
DepthSpec (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0) []
numSubs :: HashMap CommoditySymbol Int
numSubs = [CommoditySymbol] -> HashMap CommoditySymbol Int
subaccountTallies ([CommoditySymbol] -> HashMap CommoditySymbol Int)
-> (HashMap CommoditySymbol (Map DateSpan Account)
-> [CommoditySymbol])
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap CommoditySymbol (Map DateSpan Account) -> [CommoditySymbol]
forall k v. HashMap k v -> [k]
HM.keys (HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol Int)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol Int
forall a b. (a -> b) -> a -> b
$ (CommoditySymbol -> Map DateSpan Account -> Bool)
-> HashMap CommoditySymbol (Map DateSpan Account)
-> HashMap CommoditySymbol (Map DateSpan Account)
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
HM.filterWithKey CommoditySymbol -> Map DateSpan Account -> Bool
forall {t :: * -> *}.
Foldable t =>
CommoditySymbol -> t Account -> Bool
isInteresting HashMap CommoditySymbol (Map DateSpan Account)
valuedaccts
sortRows :: ReportOpts -> Journal -> [MultiBalanceReportRow] -> [MultiBalanceReportRow]
sortRows :: ReportOpts
-> Journal
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortRows ReportOpts
ropts Journal
j
| ReportOpts -> Bool
sort_amount_ ReportOpts
ropts, AccountListMode
ALTree <- ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts = [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortTreeMBRByAmount
| ReportOpts -> Bool
sort_amount_ ReportOpts
ropts, AccountListMode
ALFlat <- ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts = [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortFlatMBRByAmount
| Bool
otherwise = [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortMBRByAccountDeclaration
where
sortTreeMBRByAmount :: [MultiBalanceReportRow] -> [MultiBalanceReportRow]
sortTreeMBRByAmount :: [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortTreeMBRByAmount [PeriodicReportRow DisplayName MixedAmount]
rows = (CommoditySymbol
-> Maybe (PeriodicReportRow DisplayName MixedAmount))
-> [CommoditySymbol] -> [PeriodicReportRow DisplayName MixedAmount]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (CommoditySymbol
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
-> Maybe (PeriodicReportRow DisplayName MixedAmount)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HM.lookup` HashMap CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
rowMap) [CommoditySymbol]
sortedanames
where
accounttree :: Account
accounttree = CommoditySymbol -> [CommoditySymbol] -> Account
accountTree CommoditySymbol
"root" ([CommoditySymbol] -> Account) -> [CommoditySymbol] -> Account
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol)
-> [PeriodicReportRow DisplayName MixedAmount] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName [PeriodicReportRow DisplayName MixedAmount]
rows
rowMap :: HashMap CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
rowMap = [(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount))
-> [(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, PeriodicReportRow DisplayName MixedAmount))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
forall a b. (a -> b) -> [a] -> [b]
map (\PeriodicReportRow DisplayName MixedAmount
row -> (PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName MixedAmount
row, PeriodicReportRow DisplayName MixedAmount
row)) [PeriodicReportRow DisplayName MixedAmount]
rows
accounttreewithbals :: Account
accounttreewithbals = (Account -> Account) -> Account -> Account
mapAccounts Account -> Account
setibalance Account
accounttree
setibalance :: Account -> Account
setibalance Account
a = Account
a{aibalance = maybe (maSum . map aibalance $ asubs a) prrTotal $
HM.lookup (aname a) rowMap}
sortedaccounttree :: Account
sortedaccounttree = NormalSign -> Account -> Account
sortAccountTreeByAmount (NormalSign -> Maybe NormalSign -> NormalSign
forall a. a -> Maybe a -> a
fromMaybe NormalSign
NormallyPositive (Maybe NormalSign -> NormalSign) -> Maybe NormalSign -> NormalSign
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Maybe NormalSign
normalbalance_ ReportOpts
ropts) Account
accounttreewithbals
sortedanames :: [CommoditySymbol]
sortedanames = (Account -> CommoditySymbol) -> [Account] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map Account -> CommoditySymbol
aname ([Account] -> [CommoditySymbol]) -> [Account] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ Int -> [Account] -> [Account]
forall a. Int -> [a] -> [a]
drop Int
1 ([Account] -> [Account]) -> [Account] -> [Account]
forall a b. (a -> b) -> a -> b
$ Account -> [Account]
flattenAccounts Account
sortedaccounttree
sortFlatMBRByAmount :: [MultiBalanceReportRow] -> [MultiBalanceReportRow]
sortFlatMBRByAmount :: [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortFlatMBRByAmount = case NormalSign -> Maybe NormalSign -> NormalSign
forall a. a -> Maybe a -> a
fromMaybe NormalSign
NormallyPositive (Maybe NormalSign -> NormalSign) -> Maybe NormalSign -> NormalSign
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Maybe NormalSign
normalbalance_ ReportOpts
ropts of
NormalSign
NormallyPositive -> (PeriodicReportRow DisplayName MixedAmount
-> (Down MixedAmount, CommoditySymbol))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (\PeriodicReportRow DisplayName MixedAmount
r -> (MixedAmount -> Down MixedAmount
forall a. a -> Down a
Down (MixedAmount -> Down MixedAmount)
-> MixedAmount -> Down MixedAmount
forall a b. (a -> b) -> a -> b
$ PeriodicReportRow DisplayName MixedAmount -> MixedAmount
forall {a}. PeriodicReportRow a MixedAmount -> MixedAmount
amt PeriodicReportRow DisplayName MixedAmount
r, PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName MixedAmount
r))
NormalSign
NormallyNegative -> (PeriodicReportRow DisplayName MixedAmount
-> (MixedAmount, CommoditySymbol))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (\PeriodicReportRow DisplayName MixedAmount
r -> (PeriodicReportRow DisplayName MixedAmount -> MixedAmount
forall {a}. PeriodicReportRow a MixedAmount -> MixedAmount
amt PeriodicReportRow DisplayName MixedAmount
r, PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName MixedAmount
r))
where amt :: PeriodicReportRow a MixedAmount -> MixedAmount
amt = MixedAmount -> MixedAmount
mixedAmountStripCosts (MixedAmount -> MixedAmount)
-> (PeriodicReportRow a MixedAmount -> MixedAmount)
-> PeriodicReportRow a MixedAmount
-> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicReportRow a MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal
sortMBRByAccountDeclaration :: [MultiBalanceReportRow] -> [MultiBalanceReportRow]
sortMBRByAccountDeclaration :: [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
sortMBRByAccountDeclaration [PeriodicReportRow DisplayName MixedAmount]
rows = [CommoditySymbol]
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall b.
[CommoditySymbol]
-> [PeriodicReportRow DisplayName b]
-> [PeriodicReportRow DisplayName b]
sortRowsLike [CommoditySymbol]
sortedanames [PeriodicReportRow DisplayName MixedAmount]
rows
where
sortedanames :: [CommoditySymbol]
sortedanames = Journal -> Bool -> [CommoditySymbol] -> [CommoditySymbol]
sortAccountNamesByDeclaration Journal
j (ReportOpts -> Bool
tree_ ReportOpts
ropts) ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol)
-> [PeriodicReportRow DisplayName MixedAmount] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName [PeriodicReportRow DisplayName MixedAmount]
rows
calculateTotalsRow :: ReportOpts -> [MultiBalanceReportRow] -> Int -> PeriodicReportRow () MixedAmount
calculateTotalsRow :: ReportOpts
-> [PeriodicReportRow DisplayName MixedAmount]
-> Int
-> PeriodicReportRow () MixedAmount
calculateTotalsRow ReportOpts
ropts [PeriodicReportRow DisplayName MixedAmount]
rows Int
colcount =
()
-> [MixedAmount]
-> MixedAmount
-> MixedAmount
-> PeriodicReportRow () MixedAmount
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow () [MixedAmount]
coltotals MixedAmount
grandtotal MixedAmount
grandaverage
where
isTopRow :: PeriodicReportRow DisplayName a -> Bool
isTopRow PeriodicReportRow DisplayName a
row = ReportOpts -> Bool
flat_ ReportOpts
ropts Bool -> Bool -> Bool
|| Bool -> Bool
not ((CommoditySymbol -> Bool) -> [CommoditySymbol] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (CommoditySymbol
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
-> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`HM.member` HashMap CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
rowMap) [CommoditySymbol]
parents)
where parents :: [CommoditySymbol]
parents = [CommoditySymbol] -> [CommoditySymbol]
forall a. HasCallStack => [a] -> [a]
init ([CommoditySymbol] -> [CommoditySymbol])
-> (CommoditySymbol -> [CommoditySymbol])
-> CommoditySymbol
-> [CommoditySymbol]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommoditySymbol -> [CommoditySymbol]
expandAccountName (CommoditySymbol -> [CommoditySymbol])
-> CommoditySymbol -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ PeriodicReportRow DisplayName a -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName a
row
rowMap :: HashMap CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
rowMap = [(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount))
-> [(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
-> HashMap
CommoditySymbol (PeriodicReportRow DisplayName MixedAmount)
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, PeriodicReportRow DisplayName MixedAmount))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [(CommoditySymbol, PeriodicReportRow DisplayName MixedAmount)]
forall a b. (a -> b) -> [a] -> [b]
map (\PeriodicReportRow DisplayName MixedAmount
row -> (PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName MixedAmount
row, PeriodicReportRow DisplayName MixedAmount
row)) [PeriodicReportRow DisplayName MixedAmount]
rows
colamts :: [[MixedAmount]]
colamts = [[MixedAmount]] -> [[MixedAmount]]
forall a. [[a]] -> [[a]]
transpose ([[MixedAmount]] -> [[MixedAmount]])
-> ([PeriodicReportRow DisplayName MixedAmount] -> [[MixedAmount]])
-> [PeriodicReportRow DisplayName MixedAmount]
-> [[MixedAmount]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PeriodicReportRow DisplayName MixedAmount -> [MixedAmount])
-> [PeriodicReportRow DisplayName MixedAmount] -> [[MixedAmount]]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount -> [MixedAmount]
forall a b. PeriodicReportRow a b -> [b]
prrAmounts ([PeriodicReportRow DisplayName MixedAmount] -> [[MixedAmount]])
-> [PeriodicReportRow DisplayName MixedAmount] -> [[MixedAmount]]
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName MixedAmount -> Bool)
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a. (a -> Bool) -> [a] -> [a]
filter PeriodicReportRow DisplayName MixedAmount -> Bool
forall {a}. PeriodicReportRow DisplayName a -> Bool
isTopRow [PeriodicReportRow DisplayName MixedAmount]
rows
[MixedAmount]
coltotals :: [MixedAmount] = [Char] -> [MixedAmount] -> [MixedAmount]
forall a. Show a => [Char] -> a -> a
dbg5 [Char]
"coltotals" ([MixedAmount] -> [MixedAmount]) -> [MixedAmount] -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$ case [[MixedAmount]]
colamts of
[] -> Int -> MixedAmount -> [MixedAmount]
forall a. Int -> a -> [a]
replicate Int
colcount MixedAmount
nullmixedamt
[[MixedAmount]]
_ -> ([MixedAmount] -> MixedAmount) -> [[MixedAmount]] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map [MixedAmount] -> MixedAmount
forall (t :: * -> *). Foldable t => t MixedAmount -> MixedAmount
maSum [[MixedAmount]]
colamts
grandtotal :: MixedAmount
grandtotal = case ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts of
BalanceAccumulation
PerPeriod -> [MixedAmount] -> MixedAmount
forall (t :: * -> *). Foldable t => t MixedAmount -> MixedAmount
maSum [MixedAmount]
coltotals
BalanceAccumulation
_ -> MixedAmount -> [MixedAmount] -> MixedAmount
forall a. a -> [a] -> a
lastDef MixedAmount
nullmixedamt [MixedAmount]
coltotals
grandaverage :: MixedAmount
grandaverage = [MixedAmount] -> MixedAmount
averageMixedAmounts [MixedAmount]
coltotals
reportPercent :: ReportOpts -> MultiBalanceReport -> MultiBalanceReport
reportPercent :: ReportOpts -> MultiBalanceReport -> MultiBalanceReport
reportPercent ReportOpts
ropts report :: MultiBalanceReport
report@(PeriodicReport [DateSpan]
spans [PeriodicReportRow DisplayName MixedAmount]
rows PeriodicReportRow () MixedAmount
totalrow)
| ReportOpts -> Bool
percent_ ReportOpts
ropts = [DateSpan]
-> [PeriodicReportRow DisplayName MixedAmount]
-> PeriodicReportRow () MixedAmount
-> MultiBalanceReport
forall a b.
[DateSpan]
-> [PeriodicReportRow a b]
-> PeriodicReportRow () b
-> PeriodicReport a b
PeriodicReport [DateSpan]
spans ((PeriodicReportRow DisplayName MixedAmount
-> PeriodicReportRow DisplayName MixedAmount)
-> [PeriodicReportRow DisplayName MixedAmount]
-> [PeriodicReportRow DisplayName MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount
-> PeriodicReportRow DisplayName MixedAmount
forall {a}.
PeriodicReportRow a MixedAmount -> PeriodicReportRow a MixedAmount
percentRow [PeriodicReportRow DisplayName MixedAmount]
rows) (PeriodicReportRow () MixedAmount
-> PeriodicReportRow () MixedAmount
forall {a}.
PeriodicReportRow a MixedAmount -> PeriodicReportRow a MixedAmount
percentRow PeriodicReportRow () MixedAmount
totalrow)
| Bool
otherwise = MultiBalanceReport
report
where
percentRow :: PeriodicReportRow a MixedAmount -> PeriodicReportRow a MixedAmount
percentRow (PeriodicReportRow a
name [MixedAmount]
rowvals MixedAmount
rowtotal MixedAmount
rowavg) =
a
-> [MixedAmount]
-> MixedAmount
-> MixedAmount
-> PeriodicReportRow a MixedAmount
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow a
name
((MixedAmount -> MixedAmount -> MixedAmount)
-> [MixedAmount] -> [MixedAmount] -> [MixedAmount]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith MixedAmount -> MixedAmount -> MixedAmount
perdivide [MixedAmount]
rowvals ([MixedAmount] -> [MixedAmount]) -> [MixedAmount] -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$ PeriodicReportRow () MixedAmount -> [MixedAmount]
forall a b. PeriodicReportRow a b -> [b]
prrAmounts PeriodicReportRow () MixedAmount
totalrow)
(MixedAmount -> MixedAmount -> MixedAmount
perdivide MixedAmount
rowtotal (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal PeriodicReportRow () MixedAmount
totalrow)
(MixedAmount -> MixedAmount -> MixedAmount
perdivide MixedAmount
rowavg (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrAverage PeriodicReportRow () MixedAmount
totalrow)
transposeMap :: [(DateSpan, HashMap AccountName a)]
-> HashMap AccountName (Map DateSpan a)
transposeMap :: forall a.
[(DateSpan, HashMap CommoditySymbol a)]
-> HashMap CommoditySymbol (Map DateSpan a)
transposeMap = ((DateSpan, HashMap CommoditySymbol a)
-> HashMap CommoditySymbol (Map DateSpan a)
-> HashMap CommoditySymbol (Map DateSpan a))
-> HashMap CommoditySymbol (Map DateSpan a)
-> [(DateSpan, HashMap CommoditySymbol a)]
-> HashMap CommoditySymbol (Map DateSpan a)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((DateSpan
-> HashMap CommoditySymbol a
-> HashMap CommoditySymbol (Map DateSpan a)
-> HashMap CommoditySymbol (Map DateSpan a))
-> (DateSpan, HashMap CommoditySymbol a)
-> HashMap CommoditySymbol (Map DateSpan a)
-> HashMap CommoditySymbol (Map DateSpan a)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry DateSpan
-> HashMap CommoditySymbol a
-> HashMap CommoditySymbol (Map DateSpan a)
-> HashMap CommoditySymbol (Map DateSpan a)
forall {k} {p} {v}.
(Hashable k, Ord p) =>
p -> HashMap k v -> HashMap k (Map p v) -> HashMap k (Map p v)
addSpan) HashMap CommoditySymbol (Map DateSpan a)
forall a. Monoid a => a
mempty
where
addSpan :: p -> HashMap k v -> HashMap k (Map p v) -> HashMap k (Map p v)
addSpan p
spn HashMap k v
acctmap HashMap k (Map p v)
seen = (k -> v -> HashMap k (Map p v) -> HashMap k (Map p v))
-> HashMap k (Map p v) -> HashMap k v -> HashMap k (Map p v)
forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
HM.foldrWithKey (p -> k -> v -> HashMap k (Map p v) -> HashMap k (Map p v)
forall {k} {p} {p}.
(Hashable k, Ord p) =>
p -> k -> p -> HashMap k (Map p p) -> HashMap k (Map p p)
addAcctSpan p
spn) HashMap k (Map p v)
seen HashMap k v
acctmap
addAcctSpan :: p -> k -> p -> HashMap k (Map p p) -> HashMap k (Map p p)
addAcctSpan p
spn k
acct p
a = (Maybe (Map p p) -> Maybe (Map p p))
-> k -> HashMap k (Map p p) -> HashMap k (Map p p)
forall k v.
(Eq k, Hashable k) =>
(Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v
HM.alter Maybe (Map p p) -> Maybe (Map p p)
f k
acct
where f :: Maybe (Map p p) -> Maybe (Map p p)
f = Map p p -> Maybe (Map p p)
forall a. a -> Maybe a
Just (Map p p -> Maybe (Map p p))
-> (Maybe (Map p p) -> Map p p)
-> Maybe (Map p p)
-> Maybe (Map p p)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> p -> Map p p -> Map p p
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert p
spn p
a (Map p p -> Map p p)
-> (Maybe (Map p p) -> Map p p) -> Maybe (Map p p) -> Map p p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map p p -> Maybe (Map p p) -> Map p p
forall a. a -> Maybe a -> a
fromMaybe Map p p
forall a. Monoid a => a
mempty
sortRowsLike :: [AccountName] -> [PeriodicReportRow DisplayName b] -> [PeriodicReportRow DisplayName b]
sortRowsLike :: forall b.
[CommoditySymbol]
-> [PeriodicReportRow DisplayName b]
-> [PeriodicReportRow DisplayName b]
sortRowsLike [CommoditySymbol]
sortedas [PeriodicReportRow DisplayName b]
rows = (CommoditySymbol -> Maybe (PeriodicReportRow DisplayName b))
-> [CommoditySymbol] -> [PeriodicReportRow DisplayName b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (CommoditySymbol
-> HashMap CommoditySymbol (PeriodicReportRow DisplayName b)
-> Maybe (PeriodicReportRow DisplayName b)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HM.lookup` HashMap CommoditySymbol (PeriodicReportRow DisplayName b)
rowMap) [CommoditySymbol]
sortedas
where rowMap :: HashMap CommoditySymbol (PeriodicReportRow DisplayName b)
rowMap = [(CommoditySymbol, PeriodicReportRow DisplayName b)]
-> HashMap CommoditySymbol (PeriodicReportRow DisplayName b)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(CommoditySymbol, PeriodicReportRow DisplayName b)]
-> HashMap CommoditySymbol (PeriodicReportRow DisplayName b))
-> [(CommoditySymbol, PeriodicReportRow DisplayName b)]
-> HashMap CommoditySymbol (PeriodicReportRow DisplayName b)
forall a b. (a -> b) -> a -> b
$ (PeriodicReportRow DisplayName b
-> (CommoditySymbol, PeriodicReportRow DisplayName b))
-> [PeriodicReportRow DisplayName b]
-> [(CommoditySymbol, PeriodicReportRow DisplayName b)]
forall a b. (a -> b) -> [a] -> [b]
map (\PeriodicReportRow DisplayName b
row -> (PeriodicReportRow DisplayName b -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName b
row, PeriodicReportRow DisplayName b
row)) [PeriodicReportRow DisplayName b]
rows
subaccountTallies :: [AccountName] -> HashMap AccountName Int
subaccountTallies :: [CommoditySymbol] -> HashMap CommoditySymbol Int
subaccountTallies = (CommoditySymbol
-> HashMap CommoditySymbol Int -> HashMap CommoditySymbol Int)
-> HashMap CommoditySymbol Int
-> [CommoditySymbol]
-> HashMap CommoditySymbol Int
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr CommoditySymbol
-> HashMap CommoditySymbol Int -> HashMap CommoditySymbol Int
forall {v}.
Num v =>
CommoditySymbol
-> HashMap CommoditySymbol v -> HashMap CommoditySymbol v
incrementParent HashMap CommoditySymbol Int
forall a. Monoid a => a
mempty ([CommoditySymbol] -> HashMap CommoditySymbol Int)
-> ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol]
-> HashMap CommoditySymbol Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CommoditySymbol] -> [CommoditySymbol]
expandAccountNames
where incrementParent :: CommoditySymbol
-> HashMap CommoditySymbol v -> HashMap CommoditySymbol v
incrementParent CommoditySymbol
a = (v -> v -> v)
-> CommoditySymbol
-> v
-> HashMap CommoditySymbol v
-> HashMap CommoditySymbol v
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v
HM.insertWith v -> v -> v
forall a. Num a => a -> a -> a
(+) (CommoditySymbol -> CommoditySymbol
parentAccountName CommoditySymbol
a) v
1
perdivide :: MixedAmount -> MixedAmount -> MixedAmount
perdivide :: MixedAmount -> MixedAmount -> MixedAmount
perdivide MixedAmount
a MixedAmount
b = MixedAmount -> Maybe MixedAmount -> MixedAmount
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> MixedAmount
forall a. [Char] -> a
error' [Char]
errmsg) (Maybe MixedAmount -> MixedAmount)
-> Maybe MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ do
Amount
a' <- MixedAmount -> Maybe Amount
unifyMixedAmount MixedAmount
a
Amount
b' <- MixedAmount -> Maybe Amount
unifyMixedAmount MixedAmount
b
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Amount -> Bool
amountIsZero Amount
a' Bool -> Bool -> Bool
|| Amount -> Bool
amountIsZero Amount
b' Bool -> Bool -> Bool
|| Amount -> CommoditySymbol
acommodity Amount
a' CommoditySymbol -> CommoditySymbol -> Bool
forall a. Eq a => a -> a -> Bool
== Amount -> CommoditySymbol
acommodity Amount
b'
MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (MixedAmount -> Maybe MixedAmount)
-> MixedAmount -> Maybe MixedAmount
forall a b. (a -> b) -> a -> b
$ [Amount] -> MixedAmount
forall (t :: * -> *). Foldable t => t Amount -> MixedAmount
mixed [Quantity -> Amount
per (Quantity -> Amount) -> Quantity -> Amount
forall a b. (a -> b) -> a -> b
$ if Amount -> Quantity
aquantity Amount
b' Quantity -> Quantity -> Bool
forall a. Eq a => a -> a -> Bool
== Quantity
0 then Quantity
0 else Amount -> Quantity
aquantity Amount
a' Quantity -> Quantity -> Quantity
forall a. Fractional a => a -> a -> a
/ Quantity -> Quantity
forall a. Num a => a -> a
abs (Amount -> Quantity
aquantity Amount
b') Quantity -> Quantity -> Quantity
forall a. Num a => a -> a -> a
* Quantity
100]
where errmsg :: [Char]
errmsg = [Char]
"Cannot calculate percentages if accounts have different commodities (Hint: Try --cost, -V or similar flags.)"
sumAcct :: Account -> Account -> Account
sumAcct :: Account -> Account -> Account
sumAcct Account{aibalance :: Account -> MixedAmount
aibalance=MixedAmount
i1,aebalance :: Account -> MixedAmount
aebalance=MixedAmount
e1} a :: Account
a@Account{aibalance :: Account -> MixedAmount
aibalance=MixedAmount
i2,aebalance :: Account -> MixedAmount
aebalance=MixedAmount
e2} =
Account
a{aibalance = i1 `maPlus` i2, aebalance = e1 `maPlus` e2}
subtractAcct :: Account -> Account -> Account
subtractAcct :: Account -> Account -> Account
subtractAcct a :: Account
a@Account{aibalance :: Account -> MixedAmount
aibalance=MixedAmount
i1,aebalance :: Account -> MixedAmount
aebalance=MixedAmount
e1} Account{aibalance :: Account -> MixedAmount
aibalance=MixedAmount
i2,aebalance :: Account -> MixedAmount
aebalance=MixedAmount
e2} =
Account
a{aibalance = i1 `maMinus` i2, aebalance = e1 `maMinus` e2}
periodChanges :: Account -> Map k Account -> Map k Account
periodChanges :: forall k. Account -> Map k Account -> Map k Account
periodChanges Account
start Map k Account
amtmap =
[(k, Account)] -> Map k Account
forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList ([(k, Account)] -> Map k Account)
-> ([Account] -> [(k, Account)]) -> [Account] -> Map k Account
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [k] -> [Account] -> [(k, Account)]
forall a b. [a] -> [b] -> [(a, b)]
zip [k]
dates ([Account] -> Map k Account) -> [Account] -> Map k Account
forall a b. (a -> b) -> a -> b
$ (Account -> Account -> Account)
-> [Account] -> [Account] -> [Account]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Account -> Account -> Account
subtractAcct [Account]
amts (Account
startAccount -> [Account] -> [Account]
forall a. a -> [a] -> [a]
:[Account]
amts)
where ([k]
dates, [Account]
amts) = [(k, Account)] -> ([k], [Account])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(k, Account)] -> ([k], [Account]))
-> [(k, Account)] -> ([k], [Account])
forall a b. (a -> b) -> a -> b
$ Map k Account -> [(k, Account)]
forall k a. Map k a -> [(k, a)]
M.toAscList Map k Account
amtmap
cumulativeSum :: Account -> Map DateSpan Account -> Map DateSpan Account
cumulativeSum :: Account -> Map DateSpan Account -> Map DateSpan Account
cumulativeSum Account
start = (Account, Map DateSpan Account) -> Map DateSpan Account
forall a b. (a, b) -> b
snd ((Account, Map DateSpan Account) -> Map DateSpan Account)
-> (Map DateSpan Account -> (Account, Map DateSpan Account))
-> Map DateSpan Account
-> Map DateSpan Account
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Account -> Account -> (Account, Account))
-> Account
-> Map DateSpan Account
-> (Account, Map DateSpan Account)
forall a b c k. (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
M.mapAccum (\Account
a Account
b -> let s :: Account
s = Account -> Account -> Account
sumAcct Account
a Account
b in (Account
s, Account
s)) Account
start
tests_MultiBalanceReport :: TestTree
tests_MultiBalanceReport = [Char] -> [TestTree] -> TestTree
testGroup [Char]
"MultiBalanceReport" [
let
amt0 :: Amount
amt0 = Amount {acommodity :: CommoditySymbol
acommodity=CommoditySymbol
"$", aquantity :: Quantity
aquantity=Quantity
0, acost :: Maybe AmountCost
acost=Maybe AmountCost
forall a. Maybe a
Nothing,
astyle :: AmountStyle
astyle=AmountStyle {ascommodityside :: Side
ascommodityside = Side
L, ascommodityspaced :: Bool
ascommodityspaced = Bool
False, asdigitgroups :: Maybe DigitGroupStyle
asdigitgroups = Maybe DigitGroupStyle
forall a. Maybe a
Nothing,
asdecimalmark :: Maybe Char
asdecimalmark = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'.', asprecision :: AmountPrecision
asprecision = Word8 -> AmountPrecision
Precision Word8
2, asrounding :: Rounding
asrounding = Rounding
NoRounding}}
(ReportSpec
rspec,Journal
journal) gives :: (ReportSpec, Journal)
-> ([PeriodicReportRow DisplayName MixedAmount], MixedAmount)
-> IO ()
`gives` ([PeriodicReportRow DisplayName MixedAmount], MixedAmount)
r = do
let rspec' :: ReportSpec
rspec' = ReportSpec
rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
([PeriodicReportRow DisplayName MixedAmount]
eitems, MixedAmount
etotal) = ([PeriodicReportRow DisplayName MixedAmount], MixedAmount)
r
(PeriodicReport [DateSpan]
_ [PeriodicReportRow DisplayName MixedAmount]
aitems PeriodicReportRow () MixedAmount
atotal) = ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport ReportSpec
rspec' Journal
journal
showw :: PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char])
showw (PeriodicReportRow DisplayName
a [MixedAmount]
lAmt MixedAmount
amt MixedAmount
amt')
= (DisplayName -> CommoditySymbol
displayFull DisplayName
a, DisplayName -> CommoditySymbol
displayName DisplayName
a, DisplayName -> Int
displayIndent DisplayName
a, (MixedAmount -> [Char]) -> [MixedAmount] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map MixedAmount -> [Char]
showMixedAmountDebug [MixedAmount]
lAmt, MixedAmount -> [Char]
showMixedAmountDebug MixedAmount
amt, MixedAmount -> [Char]
showMixedAmountDebug MixedAmount
amt')
((PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char]))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [(CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char])]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char])
showw [PeriodicReportRow DisplayName MixedAmount]
aitems) [(CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char], [Char])]
-> [(CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char])]
-> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?= ((PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char]))
-> [PeriodicReportRow DisplayName MixedAmount]
-> [(CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char])]
forall a b. (a -> b) -> [a] -> [b]
map PeriodicReportRow DisplayName MixedAmount
-> (CommoditySymbol, CommoditySymbol, Int, [[Char]], [Char],
[Char])
showw [PeriodicReportRow DisplayName MixedAmount]
eitems)
MixedAmount -> [Char]
showMixedAmountDebug (PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal PeriodicReportRow () MixedAmount
atotal) [Char] -> [Char] -> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?= MixedAmount -> [Char]
showMixedAmountDebug MixedAmount
etotal
in
[Char] -> [TestTree] -> TestTree
testGroup [Char]
"multiBalanceReport" [
[Char] -> IO () -> TestTree
testCase [Char]
"null journal" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec, Journal
nulljournal) (ReportSpec, Journal)
-> ([PeriodicReportRow DisplayName MixedAmount], MixedAmount)
-> IO ()
`gives` ([], MixedAmount
nullmixedamt)
,[Char] -> IO () -> TestTree
testCase [Char]
"with -H on a populated period" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsReportOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balanceaccum_=Historical}}, Journal
samplejournal) (ReportSpec, Journal)
-> ([PeriodicReportRow DisplayName MixedAmount], MixedAmount)
-> IO ()
`gives`
(
[ DisplayName
-> [MixedAmount]
-> MixedAmount
-> MixedAmount
-> PeriodicReportRow DisplayName MixedAmount
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow (CommoditySymbol -> DisplayName
flatDisplayName CommoditySymbol
"assets:bank:checking") [Amount -> MixedAmount
mixedAmount (Amount -> MixedAmount) -> Amount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Quantity -> Amount
usd Quantity
1] (Amount -> MixedAmount
mixedAmount (Amount -> MixedAmount) -> Amount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Quantity -> Amount
usd Quantity
1) (Amount -> MixedAmount
mixedAmount Amount
amt0{aquantity=1})
, DisplayName
-> [MixedAmount]
-> MixedAmount
-> MixedAmount
-> PeriodicReportRow DisplayName MixedAmount
forall a b. a -> [b] -> b -> b -> PeriodicReportRow a b
PeriodicReportRow (CommoditySymbol -> DisplayName
flatDisplayName CommoditySymbol
"income:salary") [Amount -> MixedAmount
mixedAmount (Amount -> MixedAmount) -> Amount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Quantity -> Amount
usd (-Quantity
1)] (Amount -> MixedAmount
mixedAmount (Amount -> MixedAmount) -> Amount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Quantity -> Amount
usd (-Quantity
1)) (Amount -> MixedAmount
mixedAmount Amount
amt0{aquantity=(-1)})
],
Amount -> MixedAmount
mixedAmount (Amount -> MixedAmount) -> Amount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Quantity -> Amount
usd Quantity
0)
]
]