{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module AssetClass.Receivable
()
where
import qualified Data.Time as T
import qualified Cashflow as CF
import qualified Assumptions as A
import Asset as Ast
import Types
import Lib
import Util
import DateUtil
import InterestRate as IR
import qualified Data.Map as Map
import Data.List
import Data.Ratio
import Data.Maybe
import GHC.Generics
import Data.Aeson hiding (json)
import Language.Haskell.TH
import Data.Aeson.TH
import Data.Aeson.Types
import AssetClass.AssetBase
import AssetClass.AssetCashflow
import Debug.Trace
import Assumptions (AssetPerfAssumption(ReceivableAssump))
import GHC.Float.RealFracMethods (truncateFloatInteger)
import Cashflow (extendTxns)
import qualified Asset as A
debug :: c -> [Char] -> c
debug = ([Char] -> c -> c) -> c -> [Char] -> c
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Char] -> c -> c
forall a. [Char] -> a -> a
trace
buildRecoveryCfs :: StartDate -> Balance -> Maybe A.RecoveryAssumption -> Either String [CF.TsRow]
buildRecoveryCfs :: StartDate
-> Balance -> Maybe RecoveryAssumption -> Either [Char] [TsRow]
buildRecoveryCfs StartDate
_ Balance
_ Maybe RecoveryAssumption
Nothing = [TsRow] -> Either [Char] [TsRow]
forall a b. b -> Either a b
Right []
buildRecoveryCfs StartDate
sd Balance
defaultedBal (Just (A.RecoveryByDays Rational
r [(Int, Rational)]
dists))
= let
totalRecoveryAmt :: Balance
totalRecoveryAmt = Balance -> Rational -> Balance
mulBR Balance
defaultedBal Rational
r
recoveryDistribution :: [Rational]
recoveryDistribution = (Int, Rational) -> Rational
forall a b. (a, b) -> b
snd ((Int, Rational) -> Rational) -> [(Int, Rational)] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, Rational)]
dists
in
case [Rational] -> Rational
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Rational]
recoveryDistribution of
Rational
1 -> let
recoveryAmts :: [Balance]
recoveryAmts = Balance -> Rational -> Balance
mulBR Balance
totalRecoveryAmt (Rational -> Balance) -> [Rational] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rational]
recoveryDistribution
recoveryDates :: [StartDate]
recoveryDates = (\Int
x -> Integer -> StartDate -> StartDate
T.addDays (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
x)) (Int -> StartDate -> StartDate)
-> [Int] -> [StartDate -> StartDate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Int, Rational) -> Int
forall a b. (a, b) -> a
fst ((Int, Rational) -> Int) -> [(Int, Rational)] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, Rational)]
dists) [StartDate -> StartDate] -> [StartDate] -> [StartDate]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [StartDate
sd]
lossAmts :: [Balance]
lossAmts = Int -> Balance -> [Balance]
forall a. Int -> a -> [a]
replicate (Int -> Int
forall a. Enum a => a -> a
pred ([StartDate] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [StartDate]
recoveryDates)) Balance
0 [Balance] -> [Balance] -> [Balance]
forall a. [a] -> [a] -> [a]
++ [Balance
defaultedBal Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
totalRecoveryAmt]
in
[TsRow] -> Either [Char] [TsRow]
forall a b. b -> Either a b
Right ([TsRow] -> Either [Char] [TsRow])
-> [TsRow] -> Either [Char] [TsRow]
forall a b. (a -> b) -> a -> b
$ [ StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
d Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Balance
amt Balance
lossAmt Maybe CumulativeStat
forall a. Maybe a
Nothing | (Balance
amt,StartDate
d,Balance
lossAmt) <- [Balance]
-> [StartDate] -> [Balance] -> [(Balance, StartDate, Balance)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Balance]
recoveryAmts [StartDate]
recoveryDates [Balance]
lossAmts]
Rational
_ -> [Char] -> Either [Char] [TsRow]
forall a b. a -> Either a b
Left ([Char] -> Either [Char] [TsRow])
-> [Char] -> Either [Char] [TsRow]
forall a b. (a -> b) -> a -> b
$ [Char]
"Recovery distribution does not sum up to 1, got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Rational -> [Char]
forall a. Show a => a -> [Char]
show ([Rational] -> Rational
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Rational]
recoveryDistribution) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [(Int, Rational)] -> [Char]
forall a. Show a => a -> [Char]
show [(Int, Rational)]
dists
calcDueFactorFee :: Receivable -> Date -> Balance
calcDueFactorFee :: Receivable -> StartDate -> Balance
calcDueFactorFee r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
obr) Status
st) StartDate
asOfDay
= case Maybe ReceivableFeeType
ft of
Maybe ReceivableFeeType
Nothing -> Balance
0
Just (FixedFee Balance
b) -> Balance
b
Just (FixedRateFee Rational
r) -> Balance -> Rational -> Balance
mulBR Balance
ob Rational
r
Just (FactorFee Rational
r Int
daysInPeriod Direction
rnd) ->
let
periods :: Int
periods = case Direction
rnd of
Direction
Up -> Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling ((Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StartDate -> StartDate -> Integer
daysBetween StartDate
sd StartDate
dd)) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
daysInPeriod)) :: Int
Direction
Down -> Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor ((Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StartDate -> StartDate -> Integer
daysBetween StartDate
sd StartDate
dd)) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
daysInPeriod)) :: Int
in
Rational -> Balance
forall a. Fractional a => Rational -> a
fromRational (Rational -> Balance) -> Rational -> Balance
forall a b. (a -> b) -> a -> b
$ (Int -> Rational
forall a. Real a => a -> Rational
toRational Int
periods) Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Balance -> Rational
forall a. Real a => a -> Rational
toRational (Balance -> Rational -> Balance
mulBR Balance
ob Rational
r)
Just (AdvanceFee Rational
r) -> Balance -> Rational -> Balance
mulBR Balance
oa (Rational
r Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (DayCount -> StartDate -> StartDate -> Rational
yearCountFraction DayCount
DC_ACT_365F StartDate
sd StartDate
dd))
Just (CompoundFee [ReceivableFeeType]
fs) ->
let
newReceivables :: [Receivable]
newReceivables = [ OriginalInfo -> Status -> Receivable
Invoice (StartDate
-> Balance
-> Balance
-> StartDate
-> Maybe ReceivableFeeType
-> Maybe Obligor
-> OriginalInfo
ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd (ReceivableFeeType -> Maybe ReceivableFeeType
forall a. a -> Maybe a
Just ReceivableFeeType
newFeeType) Maybe Obligor
obr) Status
st | ReceivableFeeType
newFeeType <- [ReceivableFeeType]
fs]
in
[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
$ (Receivable -> StartDate -> Balance
`calcDueFactorFee` StartDate
asOfDay) (Receivable -> Balance) -> [Receivable] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Receivable]
newReceivables
instance Asset Receivable where
getPaymentDates :: Receivable -> Int -> [StartDate]
getPaymentDates r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
st) Int
_ = [StartDate
dd]
calcCashflow :: Receivable
-> StartDate
-> Maybe [RateAssumption]
-> Either [Char] CashFlowFrame
calcCashflow r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
st) StartDate
asOfDay Maybe [RateAssumption]
_
= CashFlowFrame -> Either [Char] CashFlowFrame
forall a b. b -> Either a b
Right (CashFlowFrame -> Either [Char] CashFlowFrame)
-> CashFlowFrame -> Either [Char] CashFlowFrame
forall a b. (a -> b) -> a -> b
$ BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Balance
ob,StartDate
asOfDay,Maybe Balance
forall a. Maybe a
Nothing) ([TsRow] -> CashFlowFrame) -> [TsRow] -> CashFlowFrame
forall a b. (a -> b) -> a -> b
$ CutoffType -> DateDirection -> StartDate -> [TsRow] -> [TsRow]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> StartDate -> [ts] -> [ts]
cutBy CutoffType
Inc DateDirection
Future StartDate
asOfDay [TsRow]
txns
where
payDate :: StartDate
payDate = StartDate
dd
feeDue :: Balance
feeDue = Receivable -> StartDate -> Balance
calcDueFactorFee Receivable
r StartDate
payDate
initTxn :: TsRow
initTxn = StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
sd Balance
ob Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Maybe CumulativeStat
forall a. Maybe a
Nothing
feePaid :: Balance
feePaid = Balance -> Balance -> Balance
forall a. Ord a => a -> a -> a
min Balance
ob Balance
feeDue
principal :: Balance
principal = Balance -> Balance -> Balance
forall a. Ord a => a -> a -> a
max Balance
0 (Balance -> Balance) -> Balance -> Balance
forall a b. (a -> b) -> a -> b
$ Balance
ob Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
feeDue
txns :: [TsRow]
txns = [TsRow
initTxn,StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
payDate Balance
0 Balance
0 Balance
principal Balance
feePaid Balance
0 Balance
0 Balance
0 Maybe CumulativeStat
forall a. Maybe a
Nothing]
getCurrentBal :: Receivable -> Balance
getCurrentBal r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
st) = Balance
ob
isDefaulted :: Receivable -> Bool
isDefaulted r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
Current) = Bool
False
isDefaulted r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
_) = Bool
True
getOriginDate :: Receivable -> StartDate
getOriginDate r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
st) = StartDate
sd
resetToOrig :: Receivable -> Receivable
resetToOrig r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
st) = Receivable
r
getRemainTerms :: Receivable -> Int
getRemainTerms r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
st) = Int
1
getOriginRate :: Receivable -> IRate
getOriginRate Receivable
_ = IRate
0
getCurrentRate :: Receivable -> IRate
getCurrentRate Receivable
_ = IRate
0
updateOriginDate :: Receivable -> StartDate -> Receivable
updateOriginDate r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
obr) Status
st) StartDate
newDate
= let
gaps :: Integer
gaps = StartDate -> StartDate -> Integer
daysBetween StartDate
sd StartDate
dd
in
OriginalInfo -> Status -> Receivable
Invoice (StartDate
-> Balance
-> Balance
-> StartDate
-> Maybe ReceivableFeeType
-> Maybe Obligor
-> OriginalInfo
ReceivableInfo StartDate
newDate Balance
ob Balance
oa (Integer -> StartDate -> StartDate
T.addDays Integer
gaps StartDate
newDate) Maybe ReceivableFeeType
ft Maybe Obligor
obr) Status
st
splitWith :: Receivable -> [Rational] -> [Receivable]
splitWith r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
obr) Status
st) [Rational]
rs
= [ OriginalInfo -> Status -> Receivable
Invoice (StartDate
-> Balance
-> Balance
-> StartDate
-> Maybe ReceivableFeeType
-> Maybe Obligor
-> OriginalInfo
ReceivableInfo StartDate
sd (Balance -> Rational -> Balance
mulBR Balance
ob Rational
ratio) (Balance -> Rational -> Balance
mulBR Balance
oa Rational
ratio) StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
obr) Status
st | Rational
ratio <- [Rational]
rs ]
projCashflow :: Receivable
-> StartDate
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
projCashflow r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) (Defaulted Maybe StartDate
_))
StartDate
asOfDay
massump :: AssetPerf
massump@(A.ReceivableAssump Maybe AssetDefaultAssumption
_ Maybe RecoveryAssumption
amr Maybe ExtraStress
ams, AssetDelinqPerfAssumption
_ , AssetDefaultedPerfAssumption
_)
Maybe [RateAssumption]
mRates
= (CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a b. b -> Either a b
Right ((CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance))
-> (CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a b. (a -> b) -> a -> b
$ (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Balance
ob,StartDate
asOfDay,Maybe Balance
forall a. Maybe a
Nothing) [TsRow]
futureTxns, Map CutoffFields Balance
historyM)
where
payDate :: StartDate
payDate = StartDate
dd
initTxn :: TsRow
initTxn = StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
sd Balance
ob Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Maybe CumulativeStat
forall a. Maybe a
Nothing
txns :: [TsRow]
txns = [TsRow
initTxn, StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
asOfDay Balance
0 Balance
0 Balance
0 Balance
0 Balance
ob Balance
0 Balance
ob Maybe CumulativeStat
forall a. Maybe a
Nothing]
([TsRow]
futureTxns,Map CutoffFields Balance
historyM)= StartDate -> [TsRow] -> ([TsRow], Map CutoffFields Balance)
CF.cutoffTrs StartDate
asOfDay ([TsRow] -> Maybe RecoveryAssumption -> [TsRow]
patchLossRecovery [TsRow]
txns Maybe RecoveryAssumption
amr)
projCashflow r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
Current)
StartDate
asOfDay
massump :: AssetPerf
massump@(A.ReceivableAssump (Just AssetDefaultAssumption
A.DefaultAtEnd) Maybe RecoveryAssumption
amr Maybe ExtraStress
ams, AssetDelinqPerfAssumption
_ , AssetDefaultedPerfAssumption
_)
Maybe [RateAssumption]
mRates
= let
payDate :: StartDate
payDate = StartDate
dd
feeDue :: Balance
feeDue = Receivable -> StartDate -> Balance
calcDueFactorFee Receivable
r StartDate
payDate
realizedLoss :: Balance
realizedLoss = case Maybe RecoveryAssumption
amr of
Maybe RecoveryAssumption
Nothing -> Balance
ob
Just RecoveryAssumption
_ -> Balance
0
txns :: [TsRow]
txns = [StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
payDate Balance
0 Balance
0 Balance
0 Balance
0 Balance
ob Balance
0 Balance
realizedLoss Maybe CumulativeStat
forall a. Maybe a
Nothing]
in
do
[TsRow]
recoveryFlow <- StartDate
-> Balance -> Maybe RecoveryAssumption -> Either [Char] [TsRow]
buildRecoveryCfs StartDate
payDate Balance
ob Maybe RecoveryAssumption
amr
let ([TsRow]
futureTxns,Map CutoffFields Balance
historyM) = StartDate -> [TsRow] -> ([TsRow], Map CutoffFields Balance)
CF.cutoffTrs StartDate
asOfDay ([TsRow] -> ([TsRow], Map CutoffFields Balance))
-> [TsRow] -> ([TsRow], Map CutoffFields Balance)
forall a b. (a -> b) -> a -> b
$ [TsRow]
txns[TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++[TsRow]
recoveryFlow
(CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a. a -> Either [Char] a
forall (m :: * -> *) a. Monad m => a -> m a
return ((CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance))
-> (CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a b. (a -> b) -> a -> b
$ (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Balance
ob,StartDate
asOfDay,Maybe Balance
forall a. Maybe a
Nothing) [TsRow]
futureTxns, Map CutoffFields Balance
historyM)
projCashflow r :: Receivable
r@(Invoice (ReceivableInfo StartDate
sd Balance
ob Balance
oa StartDate
dd Maybe ReceivableFeeType
ft Maybe Obligor
_) Status
Current)
StartDate
asOfDay
massump :: AssetPerf
massump@(A.ReceivableAssump Maybe AssetDefaultAssumption
amd Maybe RecoveryAssumption
amr Maybe ExtraStress
ams, AssetDelinqPerfAssumption
_ , AssetDefaultedPerfAssumption
_)
Maybe [RateAssumption]
mRates
= let
payDate :: StartDate
payDate = StartDate
dd
feeDue :: Balance
feeDue = Receivable -> StartDate -> Balance
calcDueFactorFee Receivable
r StartDate
payDate
initTxn :: TsRow
initTxn = StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
sd Balance
ob Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Balance
0 Maybe CumulativeStat
forall a. Maybe a
Nothing
in
do
[Rational]
defaultRates <- Receivable
-> [StartDate]
-> Maybe AssetDefaultAssumption
-> Either [Char] [Rational]
forall b.
Asset b =>
b
-> [StartDate]
-> Maybe AssetDefaultAssumption
-> Either [Char] [Rational]
A.buildDefaultRates Receivable
r (StartDate
sdStartDate -> [StartDate] -> [StartDate]
forall a. a -> [a] -> [a]
:[StartDate
dd]) Maybe AssetDefaultAssumption
amd
let defaultAmt :: Balance
defaultAmt = Balance -> Rational -> Balance
mulBR Balance
ob ([Rational] -> Rational
forall a. HasCallStack => [a] -> a
head [Rational]
defaultRates)
let afterDefaultBal :: Balance
afterDefaultBal = Balance
ob Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
defaultAmt
let afterDefaultFee :: Balance
afterDefaultFee = Balance -> Rational -> Balance
mulBR Balance
feeDue (Rational
1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- [Rational] -> Rational
forall a. HasCallStack => [a] -> a
head [Rational]
defaultRates)
let feePaid :: Balance
feePaid = Balance -> Balance -> Balance
forall a. Ord a => a -> a -> a
min Balance
afterDefaultBal Balance
afterDefaultFee
let principal :: Balance
principal = Balance -> Balance -> Balance
forall a. Ord a => a -> a -> a
max Balance
0 (Balance -> Balance) -> Balance -> Balance
forall a b. (a -> b) -> a -> b
$ Balance
afterDefaultBal Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
feePaid
let realizedLoss :: Balance
realizedLoss = case Maybe RecoveryAssumption
amr of
Maybe RecoveryAssumption
Nothing -> Balance
defaultAmt
Just RecoveryAssumption
_ -> Balance
0
let txns :: [TsRow]
txns = [TsRow
initTxn, StartDate
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Balance
-> Maybe CumulativeStat
-> TsRow
CF.ReceivableFlow StartDate
payDate Balance
0 Balance
0 Balance
principal Balance
feePaid Balance
defaultAmt Balance
0 Balance
realizedLoss Maybe CumulativeStat
forall a. Maybe a
Nothing]
[TsRow]
recoveryFlow <- StartDate
-> Balance -> Maybe RecoveryAssumption -> Either [Char] [TsRow]
buildRecoveryCfs StartDate
payDate Balance
defaultAmt Maybe RecoveryAssumption
amr
let ([TsRow]
futureTxns,Map CutoffFields Balance
historyM) = StartDate -> [TsRow] -> ([TsRow], Map CutoffFields Balance)
CF.cutoffTrs StartDate
asOfDay ([TsRow] -> ([TsRow], Map CutoffFields Balance))
-> [TsRow] -> ([TsRow], Map CutoffFields Balance)
forall a b. (a -> b) -> a -> b
$ [TsRow]
txns[TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++[TsRow]
recoveryFlow
(CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a. a -> Either [Char] a
forall (m :: * -> *) a. Monad m => a -> m a
return ((CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance))
-> (CashFlowFrame, Map CutoffFields Balance)
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a b. (a -> b) -> a -> b
$ (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Balance
ob,StartDate
asOfDay,Maybe Balance
forall a. Maybe a
Nothing) [TsRow]
futureTxns, Map CutoffFields Balance
historyM)
projCashflow Receivable
a StartDate
b AssetPerf
c Maybe [RateAssumption]
d = [Char] -> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a b. a -> Either a b
Left ([Char] -> Either [Char] (CashFlowFrame, Map CutoffFields Balance))
-> [Char]
-> Either [Char] (CashFlowFrame, Map CutoffFields Balance)
forall a b. (a -> b) -> a -> b
$ [Char]
"Failed to match when proj receivable with assumption >>" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Receivable -> [Char]
forall a. Show a => a -> [Char]
show Receivable
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ StartDate -> [Char]
forall a. Show a => a -> [Char]
show StartDate
b [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ AssetPerf -> [Char]
forall a. Show a => a -> [Char]
show AssetPerf
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Maybe [RateAssumption] -> [Char]
forall a. Show a => a -> [Char]
show Maybe [RateAssumption]
d