This upgrades Account to enable it to store a multiperiod balance, with a separate balance for each date period. This enables it do the hard work in MultiBalanceReport. Some new types are created to enable convenient operation of accounts. - `BalanceData` is a type which stores an exclusive balance, inclusive balance, and number of postings. This was previously directly stored in Account, but is now factored into a separate data type. - `PeriodData` is a container which stores date-indexed data, as well as pre-period data. In post cases, this represents the report spans, along with the historical data. - Account becomes polymorphic, allowing customisation of the type of data it stores. This will usually be `BalanceData`, but in `BudgetReport` it can use `These BalanceData BalanceData` to store both actuals and budgets in the same structure. The data structure changes to contain a `PeriodData`, allowing multiperiod accounts. Some minor changes are made to behaviour for consistency: - --declared treats parent accounts consistently. - --flat --empty ensures that implied accounts with no postings are not displayed, but accounts with zero balance and actual postings are.
60 lines
2.0 KiB
Haskell
60 lines
2.0 KiB
Haskell
{-# LANGUAGE CPP #-}
|
|
{-|
|
|
|
|
|
|
A 'BalanceData is a data type tracking a number of postings, exclusive, and inclusive balance
|
|
for given date ranges.
|
|
|
|
-}
|
|
module Hledger.Data.BalanceData
|
|
( mapBalanceData
|
|
, opBalanceData
|
|
|
|
, tests_BalanceData
|
|
) where
|
|
|
|
|
|
import Test.Tasty (testGroup)
|
|
import Test.Tasty.HUnit ((@?=), testCase)
|
|
|
|
import Hledger.Data.Amount
|
|
import Hledger.Data.Types
|
|
|
|
|
|
instance Show BalanceData where
|
|
showsPrec d (BalanceData e i n) =
|
|
showParen (d > 10) $
|
|
showString "BalanceData"
|
|
. showString "{ bdexcludingsubs = " . showString (wbUnpack (showMixedAmountB defaultFmt e))
|
|
. showString ", bdincludingsubs = " . showString (wbUnpack (showMixedAmountB defaultFmt i))
|
|
. showString ", bdnumpostings = " . shows n
|
|
. showChar '}'
|
|
|
|
instance Semigroup BalanceData where
|
|
BalanceData e i n <> BalanceData e' i' n' = BalanceData (maPlus e e') (maPlus i i') (n + n')
|
|
|
|
instance Monoid BalanceData where
|
|
mempty = BalanceData nullmixedamt nullmixedamt 0
|
|
|
|
-- | Apply an operation to both 'MixedAmount' in an 'BalanceData'.
|
|
mapBalanceData :: (MixedAmount -> MixedAmount) -> BalanceData -> BalanceData
|
|
mapBalanceData f a = a{bdexcludingsubs = f $ bdexcludingsubs a, bdincludingsubs = f $ bdincludingsubs a}
|
|
|
|
-- | Merge two 'BalanceData', using the given operation to combine their amounts.
|
|
opBalanceData :: (MixedAmount -> MixedAmount -> MixedAmount) -> BalanceData -> BalanceData -> BalanceData
|
|
opBalanceData f a b = a{bdexcludingsubs = f (bdexcludingsubs a) (bdexcludingsubs b), bdincludingsubs = f (bdincludingsubs a) (bdincludingsubs b)}
|
|
|
|
|
|
-- tests
|
|
|
|
tests_BalanceData = testGroup "BalanceData" [
|
|
|
|
testCase "opBalanceData maPlus" $ do
|
|
opBalanceData maPlus (BalanceData (mixed [usd 1]) (mixed [usd 2]) 5) (BalanceData (mixed [usd 3]) (mixed [usd 4]) 0)
|
|
@?= BalanceData (mixed [usd 4]) (mixed [usd 6]) 5,
|
|
|
|
testCase "opBalanceData maMinus" $ do
|
|
opBalanceData maMinus (BalanceData (mixed [usd 1]) (mixed [usd 2]) 5) (BalanceData (mixed [usd 3]) (mixed [usd 4]) 0)
|
|
@?= BalanceData (mixed [usd (-2)]) (mixed [usd (-2)]) 5
|
|
]
|