{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs #-}
module Reports (patchFinancialReports,getItemBalance,buildBalanceSheet,buildCashReport
) where
import Data.List ( find, sort )
import qualified Data.DList as DL
import qualified Asset as P
import qualified Data.Map as Map
import qualified Cashflow as CF
import qualified Accounts as A
import qualified CreditEnhancement as CE
import qualified Hedge as HE
import qualified Expense as F
import qualified Liability as L
import Control.Applicative (liftA3)
import Types
import Deal.DealBase
( TestDeal(TestDeal, pool, fees, bonds, accounts,liqProvider,rateSwap), getIssuanceStatsConsol, getAllCollectedFrame ,poolTypePool, dealPool)
import Deal.DealQuery ( queryCompound )
import Deal.DealAction ( calcDueFee, calcDueInt )
import Data.Maybe (fromMaybe)
import Control.Lens hiding (element)
import Control.Lens.TH
import Control.Lens
import Stmt
( aggByTxnComment,
getFlow,
getTxnComment,
getTxns,
FlowDirection(Outflow, Inflow) )
patchFinancialReports :: P.Asset a => TestDeal a -> Date -> DL.DList ResultComponent -> Either String (DL.DList ResultComponent)
patchFinancialReports :: forall a.
Asset a =>
TestDeal a
-> Date
-> DList ResultComponent
-> Either String (DList ResultComponent)
patchFinancialReports TestDeal a
t Date
d DList ResultComponent
logs
= case ((ResultComponent -> Bool)
-> [ResultComponent] -> Maybe ResultComponent
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ResultComponent -> Bool
pickReportLog ([ResultComponent] -> [ResultComponent]
forall a. [a] -> [a]
reverse (DList ResultComponent -> [ResultComponent]
forall a. DList a -> [a]
DL.toList DList ResultComponent
logs))) of
Maybe ResultComponent
Nothing -> DList ResultComponent -> Either String (DList ResultComponent)
forall a b. b -> Either a b
Right DList ResultComponent
logs
Just (FinancialReport Date
sd Date
ed BalanceSheetReport
bs CashflowReport
cash)
-> let
cashReport :: CashflowReport
cashReport = TestDeal a -> Date -> Date -> CashflowReport
forall a. Asset a => TestDeal a -> Date -> Date -> CashflowReport
buildCashReport TestDeal a
t Date
ed Date
d
in
do
BalanceSheetReport
bsReport <- TestDeal a -> Date -> Either String BalanceSheetReport
forall a.
Asset a =>
TestDeal a -> Date -> Either String BalanceSheetReport
buildBalanceSheet TestDeal a
t Date
d
let newlog :: ResultComponent
newlog = Date
-> Date -> BalanceSheetReport -> CashflowReport -> ResultComponent
FinancialReport Date
ed Date
d BalanceSheetReport
bsReport CashflowReport
cashReport
DList ResultComponent -> Either String (DList ResultComponent)
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return (DList ResultComponent -> ResultComponent -> DList ResultComponent
forall a. DList a -> a -> DList a
DL.snoc DList ResultComponent
logs ResultComponent
newlog)
where
pickReportLog :: ResultComponent -> Bool
pickReportLog FinancialReport {} = Bool
True
pickReportLog ResultComponent
_ = Bool
False
getItemBalance :: BookItem -> Balance
getItemBalance :: BookItem -> Balance
getItemBalance (Item String
_ Balance
bal) = Balance
bal
getItemBalance (ParentItem String
_ BookItems
items) = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Balance] -> Balance) -> [Balance] -> Balance
forall a b. (a -> b) -> a -> b
$ BookItem -> Balance
getItemBalance (BookItem -> Balance) -> BookItems -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BookItems
items
getPoolBalanceStats :: P.Asset a => TestDeal a -> Date -> Maybe [PoolId] -> Either String [Balance]
getPoolBalanceStats :: forall a.
Asset a =>
TestDeal a -> Date -> Maybe [PoolId] -> Either String [Balance]
getPoolBalanceStats TestDeal a
t Date
d Maybe [PoolId]
mPid
= let
poolStats :: [Either String Rational]
poolStats = [TestDeal a -> Date -> DealStats -> Either String Rational
forall a.
Asset a =>
TestDeal a -> Date -> DealStats -> Either String Rational
queryCompound TestDeal a
t Date
d (Maybe [PoolId] -> DealStats
FutureCurrentPoolBalance Maybe [PoolId]
mPid)
,(TestDeal a -> Date -> DealStats -> Either String Rational
forall a.
Asset a =>
TestDeal a -> Date -> DealStats -> Either String Rational
queryCompound TestDeal a
t Date
d ([PoolSource] -> Maybe [PoolId] -> DealStats
PoolCumCollection [PoolSource
NewDefaults] Maybe [PoolId]
mPid))
,Rational -> Rational
forall a. Num a => a -> a
negate (Rational -> Rational)
-> Either String Rational -> Either String Rational
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TestDeal a -> Date -> DealStats -> Either String Rational
forall a.
Asset a =>
TestDeal a -> Date -> DealStats -> Either String Rational
queryCompound TestDeal a
t Date
d ([PoolSource] -> Maybe [PoolId] -> DealStats
PoolCumCollection [PoolSource
CollectedRecoveries] Maybe [PoolId]
mPid))]
in
do
[Rational]
poolStats2::[Rational] <- [Either String Rational] -> Either String [Rational]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
sequenceA [Either String Rational]
poolStats
[Balance] -> Either String [Balance]
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Balance] -> Either String [Balance])
-> [Balance] -> Either String [Balance]
forall a b. (a -> b) -> a -> b
$ Rational -> Balance
forall a. Fractional a => Rational -> a
fromRational (Rational -> Balance) -> [Rational] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rational]
poolStats2
type PoolBalanceSnapshot = (Balance, Balance, Balance)
buildBalanceSheet :: P.Asset a => TestDeal a -> Date -> Either String BalanceSheetReport
buildBalanceSheet :: forall a.
Asset a =>
TestDeal a -> Date -> Either String BalanceSheetReport
buildBalanceSheet t :: TestDeal a
t@TestDeal{ pool :: forall a. TestDeal a -> PoolType a
pool = PoolType a
pool, bonds :: forall a. TestDeal a -> Map String Bond
bonds = Map String Bond
bndMap , fees :: forall a. TestDeal a -> Map String Fee
fees = Map String Fee
feeMap , liqProvider :: forall a. TestDeal a -> Maybe (Map String LiqFacility)
liqProvider = Maybe (Map String LiqFacility)
liqMap, rateSwap :: forall a. TestDeal a -> Maybe (Map String RateSwap)
rateSwap = Maybe (Map String RateSwap)
rsMap ,accounts :: forall a. TestDeal a -> Map String Account
accounts = Map String Account
accMap}
Date
d
= let
accM :: BookItems
accM = [ String -> BookItems -> BookItem
ParentItem String
accName [String -> Balance -> BookItem
Item String
"Balance" Balance
accBal,String -> Balance -> BookItem
Item String
"Accrue Int" Balance
accDue] | (String
accName, [Balance
accBal,Balance
accDue]) <- Map String [Balance] -> [(String, [Balance])]
forall k a. Map k a -> [(k, a)]
Map.toList (Map String [Balance] -> [(String, [Balance])])
-> Map String [Balance] -> [(String, [Balance])]
forall a b. (a -> b) -> a -> b
$ (Account -> [Balance])
-> Map String Account -> Map String [Balance]
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (\Account
acc -> [Account -> Balance
A.accBalance,(Date -> Account -> Balance
A.accrueInt Date
d)] [Account -> Balance] -> [Account] -> [Balance]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Account
acc]) Map String Account
accMap ]
mapPoolKey :: PoolId -> Maybe [PoolId]
mapPoolKey PoolId
PoolConsol = Maybe [PoolId]
forall a. Maybe a
Nothing
mapPoolKey (PoolName String
x) = [PoolId] -> Maybe [PoolId]
forall a. a -> Maybe a
Just [String -> PoolId
PoolName String
x]
poolAstBalMap_ :: Map PoolId (Either String [Balance])
poolAstBalMap_ = (PoolId -> Pool a -> Either String [Balance])
-> Map PoolId (Pool a) -> Map PoolId (Either String [Balance])
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey
(\PoolId
k Pool a
_ -> TestDeal a -> Date -> Maybe [PoolId] -> Either String [Balance]
forall a.
Asset a =>
TestDeal a -> Date -> Maybe [PoolId] -> Either String [Balance]
getPoolBalanceStats TestDeal a
t Date
d (PoolId -> Maybe [PoolId]
mapPoolKey PoolId
k)) (Map PoolId (Pool a) -> Map PoolId (Either String [Balance]))
-> Map PoolId (Pool a) -> Map PoolId (Either String [Balance])
forall a b. (a -> b) -> a -> b
$
Getting (Map PoolId (Pool a)) (TestDeal a) (Map PoolId (Pool a))
-> TestDeal a -> Map PoolId (Pool a)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((PoolType a -> Const (Map PoolId (Pool a)) (PoolType a))
-> TestDeal a -> Const (Map PoolId (Pool a)) (TestDeal a)
forall a. Asset a => Lens' (TestDeal a) (PoolType a)
Lens' (TestDeal a) (PoolType a)
dealPool ((PoolType a -> Const (Map PoolId (Pool a)) (PoolType a))
-> TestDeal a -> Const (Map PoolId (Pool a)) (TestDeal a))
-> ((Map PoolId (Pool a)
-> Const (Map PoolId (Pool a)) (Map PoolId (Pool a)))
-> PoolType a -> Const (Map PoolId (Pool a)) (PoolType a))
-> Getting (Map PoolId (Pool a)) (TestDeal a) (Map PoolId (Pool a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map PoolId (Pool a)
-> Const (Map PoolId (Pool a)) (Map PoolId (Pool a)))
-> PoolType a -> Const (Map PoolId (Pool a)) (PoolType a)
forall a. Asset a => Lens' (PoolType a) (Map PoolId (Pool a))
Lens' (PoolType a) (Map PoolId (Pool a))
poolTypePool) TestDeal a
t
swapToCollect :: BookItem
swapToCollect = String -> BookItems -> BookItem
ParentItem String
"Swap" [ String -> BookItems -> BookItem
ParentItem String
rsName [ String -> Balance -> BookItem
Item String
"To Receive" Balance
rsNet ] | (String
rsName,Balance
rsNet) <- Map String Balance -> [(String, Balance)]
forall k a. Map k a -> [(k, a)]
Map.toList ((RateSwap -> Balance) -> Map String RateSwap -> Map String Balance
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (RateSwap -> Balance
HE.rsNetCash (RateSwap -> Balance)
-> (RateSwap -> RateSwap) -> RateSwap -> Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Date -> RateSwap -> RateSwap
HE.accrueIRS Date
d)) (Map String RateSwap
-> Maybe (Map String RateSwap) -> Map String RateSwap
forall a. a -> Maybe a -> a
fromMaybe Map String RateSwap
forall k a. Map k a
Map.empty Maybe (Map String RateSwap)
rsMap))
, Balance
rsNet Balance -> Balance -> Bool
forall a. Ord a => a -> a -> Bool
> Balance
0 ]
liqProviderAccrued :: Map String LiqFacility
liqProviderAccrued = (LiqFacility -> LiqFacility)
-> Map String LiqFacility -> Map String LiqFacility
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (Date -> LiqFacility -> LiqFacility
CE.accrueLiqProvider Date
d) (Map String LiqFacility
-> Maybe (Map String LiqFacility) -> Map String LiqFacility
forall a. a -> Maybe a -> a
fromMaybe Map String LiqFacility
forall k a. Map k a
Map.empty Maybe (Map String LiqFacility)
liqMap)
liqProviderOs :: BookItems
liqProviderOs = [ String -> BookItems -> BookItem
ParentItem String
liqName [String -> Balance -> BookItem
Item String
"Balance" Balance
liqBal,String -> Balance -> BookItem
Item String
"Accrue Int" Balance
liqDueInt, String -> Balance -> BookItem
Item String
"Due Fee" Balance
liqDueFee ] | (String
liqName,[Balance
liqBal,Balance
liqDueInt,Balance
liqDueFee]) <- Map String [Balance] -> [(String, [Balance])]
forall k a. Map k a -> [(k, a)]
Map.toList ((LiqFacility -> [Balance])
-> Map String LiqFacility -> Map String [Balance]
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (\LiqFacility
liq -> [LiqFacility -> Balance
CE.liqBalance,LiqFacility -> Balance
CE.liqDueInt,LiqFacility -> Balance
CE.liqDuePremium][LiqFacility -> Balance] -> [LiqFacility] -> [Balance]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [LiqFacility
liq]) Map String LiqFacility
liqProviderAccrued)]
swapToPay :: BookItem
swapToPay = String -> BookItems -> BookItem
ParentItem String
"Swap" [ String -> BookItems -> BookItem
ParentItem String
rsName [String -> Balance -> BookItem
Item String
"To Pay" (Balance -> Balance
forall a. Num a => a -> a
negate Balance
rsNet)] | (String
rsName,Balance
rsNet) <- Map String Balance -> [(String, Balance)]
forall k a. Map k a -> [(k, a)]
Map.toList ((RateSwap -> Balance) -> Map String RateSwap -> Map String Balance
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (RateSwap -> Balance
HE.rsNetCash (RateSwap -> Balance)
-> (RateSwap -> RateSwap) -> RateSwap -> Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Date -> RateSwap -> RateSwap
HE.accrueIRS Date
d)) (Map String RateSwap
-> Maybe (Map String RateSwap) -> Map String RateSwap
forall a. a -> Maybe a -> a
fromMaybe Map String RateSwap
forall k a. Map k a
Map.empty Maybe (Map String RateSwap)
rsMap))
, Balance
rsNet Balance -> Balance -> Bool
forall a. Ord a => a -> a -> Bool
< Balance
0 ]
in
do
Map PoolId [Balance]
poolAstBalMap <- Map PoolId (Either String [Balance])
-> Either String (Map PoolId [Balance])
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
Map PoolId (f a) -> f (Map PoolId a)
sequenceA Map PoolId (Either String [Balance])
poolAstBalMap_
let poolAstMap :: Map PoolId BookItem
poolAstMap = (PoolId -> [Balance] -> BookItem)
-> Map PoolId [Balance] -> Map PoolId BookItem
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey
(\PoolId
k [Balance]
vs -> String -> BookItems -> BookItem
ParentItem (PoolId -> String
forall a. Show a => a -> String
show PoolId
k)
[ String -> Balance -> BookItem
Item String
"Performing" ([Balance]
vs[Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!!Int
0)
, String -> Balance -> BookItem
Item String
"Defaulted" ([Balance]
vs[Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!!Int
1)
, String -> Balance -> BookItem
Item String
"Recovery" ([Balance]
vs[Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!!Int
2) ])
Map PoolId [Balance]
poolAstBalMap
let poolAst :: BookItem
poolAst = String -> BookItems -> BookItem
ParentItem String
"Pool" (BookItems -> BookItem) -> BookItems -> BookItem
forall a b. (a -> b) -> a -> b
$ Map PoolId BookItem -> BookItems
forall k a. Map k a -> [a]
Map.elems Map PoolId BookItem
poolAstMap
let ast :: BookItem
ast = String -> BookItems -> BookItem
ParentItem String
"Asset" [String -> BookItems -> BookItem
ParentItem String
"Account" BookItems
accM , BookItem
poolAst , BookItem
swapToCollect]
Map String Balance
feeWithDueAmount <- (Fee -> Balance
F.feeDue (Fee -> Balance) -> Map String Fee -> Map String Balance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Map String Fee -> Map String Balance)
-> Either String (Map String Fee)
-> Either String (Map String Balance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Fee -> Either String Fee)
-> Map String Fee -> Either String (Map String Fee)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Map String a -> m (Map String b)
mapM ((TestDeal a -> Date -> Fee -> Either String Fee
forall a. Asset a => TestDeal a -> Date -> Fee -> Either String Fee
calcDueFee TestDeal a
t Date
d)) Map String Fee
feeMap
let feeToPay :: BookItem
feeToPay = String -> BookItems -> BookItem
ParentItem String
"Fee" [ String -> BookItems -> BookItem
ParentItem String
feeName [String -> Balance -> BookItem
Item String
"Due" Balance
feeDueBal]
| (String
feeName,Balance
feeDueBal) <- Map String Balance -> [(String, Balance)]
forall k a. Map k a -> [(k, a)]
Map.toList Map String Balance
feeWithDueAmount ]
Map String Bond
bndWithDueAmount <- (Bond -> Either String Bond)
-> Map String Bond -> Either String (Map String Bond)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Map String a -> m (Map String b)
mapM (TestDeal a -> Date -> Bond -> Either String Bond
forall a.
Asset a =>
TestDeal a -> Date -> Bond -> Either String Bond
calcDueInt TestDeal a
t Date
d) Map String Bond
bndMap
let bndToShow :: Map String (Balance, Balance)
bndToShow = (Bond -> (Balance, Balance))
-> Map String Bond -> Map String (Balance, Balance)
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (\Bond
bnd -> (Bond -> Balance
forall lb. Liable lb => lb -> Balance
L.getCurBalance Bond
bnd, Bond -> Balance
forall lb. Liable lb => lb -> Balance
L.getTotalDueInt Bond
bnd)) Map String Bond
bndWithDueAmount
let bndM :: BookItems
bndM = [ String -> BookItems -> BookItem
ParentItem String
bndName [String -> Balance -> BookItem
Item String
"Balance" Balance
bndBal,String -> Balance -> BookItem
Item String
"Due Int" Balance
bndDueAmt ]
| (String
bndName,(Balance
bndBal,Balance
bndDueAmt)) <- Map String (Balance, Balance) -> [(String, (Balance, Balance))]
forall k a. Map k a -> [(k, a)]
Map.toList Map String (Balance, Balance)
bndToShow]
let liab :: BookItem
liab = String -> BookItems -> BookItem
ParentItem String
"Liability" [ String -> BookItems -> BookItem
ParentItem String
"Bond" BookItems
bndM , BookItem
feeToPay, String -> BookItems -> BookItem
ParentItem String
"Liquidity" BookItems
liqProviderOs, BookItem
swapToPay]
let totalDebtBal :: Balance
totalDebtBal = BookItem -> Balance
getItemBalance BookItem
liab
let totalAssetBal :: Balance
totalAssetBal = BookItem -> Balance
getItemBalance BookItem
ast
let eqty :: BookItem
eqty = String -> Balance -> BookItem
Item String
"Net Asset" (Balance
totalAssetBal Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
totalDebtBal)
BalanceSheetReport -> Either String BalanceSheetReport
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return (BalanceSheetReport -> Either String BalanceSheetReport)
-> BalanceSheetReport -> Either String BalanceSheetReport
forall a b. (a -> b) -> a -> b
$ BalanceSheetReport {asset :: BookItem
asset=BookItem
ast,liability :: BookItem
liability=BookItem
liab,equity :: BookItem
equity=BookItem
eqty,reportDate :: Date
reportDate=Date
d}
buildCashReport :: P.Asset a => TestDeal a -> Date -> Date -> CashflowReport
buildCashReport :: forall a. Asset a => TestDeal a -> Date -> Date -> CashflowReport
buildCashReport t :: TestDeal a
t@TestDeal{accounts :: forall a. TestDeal a -> Map String Account
accounts = Map String Account
accs} Date
sd Date
ed
= CashflowReport { inflow :: BookItem
inflow = BookItem
inflowItems
, outflow :: BookItem
outflow = BookItem
outflowItems
, net :: BookItem
net = BookItem
cashChange
, startDate :: Date
startDate = Date
sd
, endDate :: Date
endDate = Date
ed }
where
_txns :: [Txn]
_txns = [[Txn]] -> [Txn]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Txn]] -> [Txn]) -> [[Txn]] -> [Txn]
forall a b. (a -> b) -> a -> b
$ Map String [Txn] -> [[Txn]]
forall k a. Map k a -> [a]
Map.elems (Map String [Txn] -> [[Txn]]) -> Map String [Txn] -> [[Txn]]
forall a b. (a -> b) -> a -> b
$ (Maybe Statement -> [Txn])
-> Map String (Maybe Statement) -> Map String [Txn]
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList (DList Txn -> [Txn])
-> (Maybe Statement -> DList Txn) -> Maybe Statement -> [Txn]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Statement -> DList Txn
getTxns) (Map String (Maybe Statement) -> Map String [Txn])
-> Map String (Maybe Statement) -> Map String [Txn]
forall a b. (a -> b) -> a -> b
$ (Account -> Maybe Statement)
-> Map String Account -> Map String (Maybe Statement)
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map Account -> Maybe Statement
A.accStmt Map String Account
accs
txns :: [Txn]
txns = RangeType -> Date -> Date -> [Txn] -> [Txn]
forall ts.
TimeSeries ts =>
RangeType -> Date -> Date -> [ts] -> [ts]
sliceBy RangeType
EI Date
sd Date
ed [Txn]
_txns
inflowTxn :: [Txn]
inflowTxn = [Txn] -> [Txn]
forall a. Ord a => [a] -> [a]
sort ([Txn] -> [Txn]) -> [Txn] -> [Txn]
forall a b. (a -> b) -> a -> b
$ (Txn -> Bool) -> [Txn] -> [Txn]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Txn
x -> (TxnComment -> FlowDirection
getFlow (TxnComment -> FlowDirection)
-> (Txn -> TxnComment) -> Txn -> FlowDirection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Txn -> TxnComment
getTxnComment) Txn
x FlowDirection -> FlowDirection -> Bool
forall a. Eq a => a -> a -> Bool
== FlowDirection
Inflow) [Txn]
txns
outflowTxn :: [Txn]
outflowTxn = [Txn] -> [Txn]
forall a. Ord a => [a] -> [a]
sort ([Txn] -> [Txn]) -> [Txn] -> [Txn]
forall a b. (a -> b) -> a -> b
$ (Txn -> Bool) -> [Txn] -> [Txn]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Txn
x -> (TxnComment -> FlowDirection
getFlow (TxnComment -> FlowDirection)
-> (Txn -> TxnComment) -> Txn -> FlowDirection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Txn -> TxnComment
getTxnComment) Txn
x FlowDirection -> FlowDirection -> Bool
forall a. Eq a => a -> a -> Bool
== FlowDirection
Outflow) [Txn]
txns
inflowM :: Map String Balance
inflowM = (TxnComment -> String)
-> Map TxnComment Balance -> Map String Balance
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys TxnComment -> String
forall a. Show a => a -> String
show (Map TxnComment Balance -> Map String Balance)
-> Map TxnComment Balance -> Map String Balance
forall a b. (a -> b) -> a -> b
$ [Txn] -> Map TxnComment [Txn] -> Map TxnComment Balance
aggByTxnComment [Txn]
inflowTxn Map TxnComment [Txn]
forall k a. Map k a
Map.empty
outflowM :: Map String Balance
outflowM = (TxnComment -> String)
-> Map TxnComment Balance -> Map String Balance
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys TxnComment -> String
forall a. Show a => a -> String
show (Map TxnComment Balance -> Map String Balance)
-> Map TxnComment Balance -> Map String Balance
forall a b. (a -> b) -> a -> b
$ [Txn] -> Map TxnComment [Txn] -> Map TxnComment Balance
aggByTxnComment [Txn]
outflowTxn Map TxnComment [Txn]
forall k a. Map k a
Map.empty
inflowItems :: BookItem
inflowItems = String -> BookItems -> BookItem
ParentItem String
"Inflow" [ String -> Balance -> BookItem
Item String
k Balance
v | (String
k,Balance
v) <- Map String Balance -> [(String, Balance)]
forall k a. Map k a -> [(k, a)]
Map.toList Map String Balance
inflowM ]
outflowItems :: BookItem
outflowItems = String -> BookItems -> BookItem
ParentItem String
"Outflow" [ String -> Balance -> BookItem
Item String
k Balance
v | (String
k,Balance
v) <- Map String Balance -> [(String, Balance)]
forall k a. Map k a -> [(k, a)]
Map.toList Map String Balance
outflowM ]
cashChange :: BookItem
cashChange = String -> Balance -> BookItem
Item String
"Net Cash" (Balance -> BookItem) -> Balance -> BookItem
forall a b. (a -> b) -> a -> b
$ [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (Map String Balance -> [Balance]
forall k a. Map k a -> [a]
Map.elems Map String Balance
inflowM) Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (Map String Balance -> [Balance]
forall k a. Map k a -> [a]
Map.elems Map String Balance
outflowM)