{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module AssetClass.Installment
(projectInstallmentFlow, updateOriginDate)
where
import qualified Data.Time as T
import Data.Ratio
import Data.Aeson hiding (json)
import Language.Haskell.TH
import Data.Maybe
import Data.List
import qualified Data.DList as DL
import Data.Aeson.TH
import qualified Data.Map as Map
import Data.Aeson.Types
import GHC.Generics
import Asset
import InterestRate
import qualified Assumptions as A
import Types
import Lib
import Util
import DateUtil
import qualified Cashflow as CF
import AssetClass.AssetBase
import Debug.Trace
import AssetClass.AssetCashflow
import qualified Asset as Ast
import Control.Lens hiding (element)
import Control.Lens.TH
debug :: c -> String -> c
debug = (String -> c -> c) -> c -> String -> c
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> c -> c
forall a. String -> a -> a
trace
projectInstallmentFlow :: (Balance,Date,(Balance,Balance),IRate,Rational,AmortPlan,Int) -> (Dates, [DefaultRate], [PrepaymentRate], [Int]) -> (DL.DList CF.TsRow, Balance ,Rational)
projectInstallmentFlow :: (Recovery, Date, (Recovery, Recovery), IRate, Rational, AmortPlan,
Int)
-> (Dates, [Rational], [Rational], [Int])
-> (DList TsRow, Recovery, Rational)
projectInstallmentFlow (Recovery
startBal, Date
lastPaidDate, (Recovery
originRepay,Recovery
originInt), IRate
startRate,Rational
begFactor,AmortPlan
pt,Int
ot) (Dates
cfDates, [Rational]
defRates, [Rational]
ppyRates, [Int]
remainTerms)
= let
initRow :: TsRow
initRow = Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow
CF.LoanFlow Date
lastPaidDate Recovery
startBal Recovery
0.0 Recovery
0.0 Recovery
0.0 Recovery
0.0 Recovery
0.0 Recovery
0.0 IRate
startRate Maybe CumulativeStat
forall a. Maybe a
Nothing
calcPrin :: a -> Recovery -> Recovery -> Rational -> Recovery
calcPrin a
_rt Recovery
_bal Recovery
_opmt Rational
_factor = case a
_rt of
a
1 -> Recovery
_bal
a
0 -> Recovery
0
a
_ -> Recovery -> Rational -> Recovery
mulBR Recovery
_opmt Rational
_factor
in
((DList TsRow, Recovery, Rational)
-> (Date, Rational, Rational, Int)
-> (DList TsRow, Recovery, Rational))
-> (DList TsRow, Recovery, Rational)
-> [(Date, Rational, Rational, Int)]
-> (DList TsRow, Recovery, Rational)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl
(\(DList TsRow
acc,Recovery
begBal,Rational
factor) (Date
pDate, Rational
ppyRate, Rational
defRate, Int
rt) ->
let
newDefault :: Recovery
newDefault = Recovery -> Rational -> Recovery
mulBR Recovery
begBal Rational
defRate
newPrepay :: Recovery
newPrepay = Recovery -> Rational -> Recovery
mulBR (Recovery
begBal Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
- Recovery
newDefault) Rational
ppyRate
intBal :: Recovery
intBal = Recovery
begBal Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
- Recovery
newDefault Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
- Recovery
newPrepay
newFactor :: Rational
newFactor = Rational
factor Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
-Rational
defRate) Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- Rational
ppyRate)
newInt :: Recovery
newInt = case AmortPlan
pt of
AmortPlan
F_P -> if Int
rt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then
Recovery -> Rational -> Recovery
mulBR Recovery
originInt Rational
newFactor
else
Recovery
0
PO_FirstN Int
n -> if (Int
otInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
rt) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n then
Recovery -> Rational -> Recovery
mulBR Recovery
originInt Rational
newFactor
else
Recovery
0
newPrin :: Recovery
newPrin = Int -> Recovery -> Recovery -> Rational -> Recovery
forall {a}.
(Eq a, Num a) =>
a -> Recovery -> Recovery -> Rational -> Recovery
calcPrin Int
rt Recovery
intBal Recovery
originRepay Rational
newFactor
endBal :: Recovery
endBal = Recovery
intBal Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
- Recovery
newPrin
in
(DList TsRow -> TsRow -> DList TsRow
forall a. DList a -> a -> DList a
DL.snoc DList TsRow
acc (Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow
CF.LoanFlow Date
pDate Recovery
endBal Recovery
newPrin Recovery
newInt Recovery
newPrepay Recovery
newDefault Recovery
0.0 Recovery
0.0 IRate
startRate Maybe CumulativeStat
forall a. Maybe a
Nothing)
,Recovery
endBal
,Rational
newFactor))
(TsRow -> DList TsRow
forall a. a -> DList a
DL.singleton TsRow
initRow, Recovery
startBal, Rational
begFactor)
(Dates
-> [Rational]
-> [Rational]
-> [Int]
-> [(Date, Rational, Rational, Int)]
forall a b c d. [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
zip4 Dates
cfDates [Rational]
ppyRates [Rational]
defRates [Int]
remainTerms)
instance Asset Installment where
calcCashflow :: Installment
-> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame
calcCashflow inst :: Installment
inst@(Installment (LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
ptype Maybe Obligor
_) Recovery
cb Int
rt Status
st) Date
asOfDay Maybe [RateAssumption]
_
= CashFlowFrame -> Either String CashFlowFrame
forall a b. b -> Either a b
Right (CashFlowFrame -> Either String CashFlowFrame)
-> CashFlowFrame -> Either String CashFlowFrame
forall a b. (a -> b) -> a -> b
$ BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Recovery
begBal,Date
asOfDay,Maybe Recovery
forall a. Maybe a
Nothing) [TsRow]
flows
where
Date
lastPayDate:Dates
cf_dates = Int -> Dates -> Dates
forall a. Int -> [a] -> [a]
lastN (Int
rtInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Dates -> Dates) -> Dates -> Dates
forall a b. (a -> b) -> a -> b
$ Date
sdDate -> Dates -> Dates
forall a. a -> [a] -> [a]
:Installment -> Int -> Dates
forall a. Asset a => a -> Int -> Dates
getPaymentDates Installment
inst Int
0
opmt :: Recovery
opmt = Recovery -> Int -> Recovery
divideBI Recovery
ob Int
ot
schedule_balances :: [Recovery]
schedule_balances = (Recovery -> Recovery -> Recovery)
-> Recovery -> [Recovery] -> [Recovery]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl (-) Recovery
ob (Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
ot Recovery
opmt)
current_schedule_bal :: Recovery
current_schedule_bal = [Recovery]
schedule_balances [Recovery] -> Int -> Recovery
forall a. HasCallStack => [a] -> Int -> a
!! (Int
ot Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rt)
ofee :: Recovery
ofee = Recovery -> IRate -> Recovery
mulBIR Recovery
ob (Installment -> IRate
forall a. Asset a => a -> IRate
getOriginRate Installment
inst)
factor :: Recovery
factor = Recovery
cb Recovery -> Recovery -> Recovery
forall a. Fractional a => a -> a -> a
/ Recovery
current_schedule_bal
cpmt :: Recovery
cpmt = Recovery
opmt Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
* Recovery
factor
cfee :: Recovery
cfee = Recovery
ofee Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
* Recovery
factor
orate :: IRate
orate = Installment -> IRate
forall a. Asset a => a -> IRate
getOriginRate Installment
inst
stressed_bal_flow :: [Recovery]
stressed_bal_flow = (Recovery -> Recovery) -> [Recovery] -> [Recovery]
forall a b. (a -> b) -> [a] -> [b]
map (Recovery -> Recovery -> Recovery
forall a. Num a => a -> a -> a
* Recovery
factor) ([Recovery] -> [Recovery]) -> [Recovery] -> [Recovery]
forall a b. (a -> b) -> a -> b
$ Int -> [Recovery] -> [Recovery]
forall a. Int -> [a] -> [a]
lastN Int
rt [Recovery]
schedule_balances
prin_flow :: [Recovery]
prin_flow = Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
rt Recovery
cpmt
int_flow :: [Recovery]
int_flow = case AmortPlan
ptype of
AmortPlan
F_P -> Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
rt Recovery
cfee
PO_FirstN Int
n -> Int -> [Recovery] -> [Recovery]
forall a. Int -> [a] -> [a]
lastN Int
rt ([Recovery] -> [Recovery]) -> [Recovery] -> [Recovery]
forall a b. (a -> b) -> a -> b
$ Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
n Recovery
0.0 [Recovery] -> [Recovery] -> [Recovery]
forall a. [a] -> [a] -> [a]
++ Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate (Int
otInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n) Recovery
cfee
_flows :: [TsRow]
_flows = let
_rt :: Int
_rt = Int -> Int
forall a. Enum a => a -> a
succ Int
rt
in
(Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow)
-> Dates
-> [Recovery]
-> [Recovery]
-> [Recovery]
-> [Recovery]
-> [Recovery]
-> [Recovery]
-> [Recovery]
-> [IRate]
-> [Maybe CumulativeStat]
-> [TsRow]
forall a b c d e f g h i j k.
(a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k)
-> [a]
-> [b]
-> [c]
-> [d]
-> [e]
-> [f]
-> [g]
-> [h]
-> [i]
-> [j]
-> [k]
zipWith10 Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow
CF.LoanFlow (Date
lastPayDateDate -> Dates -> Dates
forall a. a -> [a] -> [a]
:Dates
cf_dates) (Recovery
cbRecovery -> [Recovery] -> [Recovery]
forall a. a -> [a] -> [a]
:[Recovery]
stressed_bal_flow) (Recovery
0Recovery -> [Recovery] -> [Recovery]
forall a. a -> [a] -> [a]
:[Recovery]
prin_flow) (Recovery
0Recovery -> [Recovery] -> [Recovery]
forall a. a -> [a] -> [a]
:[Recovery]
int_flow)
(Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
_rt Recovery
0.0) (Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
_rt Recovery
0.0) (Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
_rt Recovery
0.0) (Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
_rt Recovery
0.0)
(Int -> IRate -> [IRate]
forall a. Int -> a -> [a]
replicate Int
_rt IRate
orate) (Int -> Maybe CumulativeStat -> [Maybe CumulativeStat]
forall a. Int -> a -> [a]
replicate Int
_rt Maybe CumulativeStat
forall a. Maybe a
Nothing)
flows :: [TsRow]
flows = CutoffType -> DateDirection -> Date -> [TsRow] -> [TsRow]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Inc DateDirection
Future Date
asOfDay [TsRow]
_flows
begBal :: Recovery
begBal = [TsRow] -> Recovery
CF.buildBegBal [TsRow]
flows
getCurrentBal :: Installment -> Recovery
getCurrentBal (Installment OriginalInfo
_ Recovery
b Int
_ Status
_ ) = Recovery
b
getOriginInfo :: Installment -> OriginalInfo
getOriginInfo (Installment OriginalInfo
oi Recovery
_ Int
_ Status
_) = OriginalInfo
oi
getOriginBal :: Installment -> Recovery
getOriginBal (Installment (LoanOriginalInfo Recovery
ob RateType
_ Int
_ Period
_ Date
_ AmortPlan
_ Maybe Obligor
_) Recovery
_ Int
_ Status
_) = Recovery
ob
getOriginRate :: Installment -> IRate
getOriginRate (Installment (LoanOriginalInfo Recovery
_ RateType
or Int
_ Period
_ Date
_ AmortPlan
_ Maybe Obligor
_) Recovery
_ Int
_ Status
_)
= case RateType
or of
Fix DayCount
_ IRate
_r -> IRate
_r
Floater DayCount
_ Index
_ IRate
_ IRate
_r DatePattern
_ RateFloor
_ RateFloor
_ Maybe (RoundingBy IRate)
_ -> IRate
_r
isDefaulted :: Installment -> Bool
isDefaulted (Installment OriginalInfo
_ Recovery
_ Int
_ (Defaulted Maybe Date
_)) = Bool
True
isDefaulted (Installment {}) = Bool
False
getPaymentDates :: Installment -> Int -> Dates
getPaymentDates (Installment (LoanOriginalInfo Recovery
_ RateType
_ Int
ot Period
p Date
sd AmortPlan
_ Maybe Obligor
_) Recovery
_ Int
_ Status
_) Int
extra
= Date -> Period -> Int -> Dates
genDates Date
sd Period
p (Int
otInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
extra)
getOriginDate :: Installment -> Date
getOriginDate (Installment (LoanOriginalInfo Recovery
_ RateType
_ Int
ot Period
p Date
sd AmortPlan
_ Maybe Obligor
_) Recovery
_ Int
_ Status
_) = Date
sd
getRemainTerms :: Installment -> Int
getRemainTerms (Installment (LoanOriginalInfo Recovery
_ RateType
_ Int
ot Period
p Date
sd AmortPlan
_ Maybe Obligor
_) Recovery
_ Int
rt Status
_) = Int
rt
updateOriginDate :: Installment -> Date -> Installment
updateOriginDate (Installment (LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
_type Maybe Obligor
_obligor) Recovery
cb Int
rt Status
st) Date
nd
= OriginalInfo -> Recovery -> Int -> Status -> Installment
Installment (Recovery
-> RateType
-> Int
-> Period
-> Date
-> AmortPlan
-> Maybe Obligor
-> OriginalInfo
LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
nd AmortPlan
_type Maybe Obligor
_obligor) Recovery
cb Int
rt Status
st
resetToOrig :: Installment -> Installment
resetToOrig (Installment (LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
_type Maybe Obligor
_obligor) Recovery
cb Int
rt Status
st)
= OriginalInfo -> Recovery -> Int -> Status -> Installment
Installment (Recovery
-> RateType
-> Int
-> Period
-> Date
-> AmortPlan
-> Maybe Obligor
-> OriginalInfo
LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
_type Maybe Obligor
_obligor) Recovery
ob Int
ot Status
st
projCashflow :: Installment
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
projCashflow inst :: Installment
inst@(Installment (LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
pt Maybe Obligor
_) Recovery
cb Int
rt Status
Current)
Date
asOfDay
pAssump :: AssetPerf
pAssump@(A.InstallmentAssump Maybe AssetDefaultAssumption
defaultAssump Maybe AssetPrepayAssumption
prepayAssump Maybe RecoveryAssumption
recoveryAssump Maybe ExtraStress
ams,AssetDelinqPerfAssumption
_,AssetDefaultedPerfAssumption
_)
Maybe [RateAssumption]
mRates
= let
recoveryLag :: Int
recoveryLag = Int
-> (RecoveryAssumption -> Int) -> Maybe RecoveryAssumption -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 RecoveryAssumption -> Int
getRecoveryLag Maybe RecoveryAssumption
recoveryAssump
Date
lastPayDate:Dates
cfDates = Int -> Dates -> Dates
forall a. Int -> [a] -> [a]
lastN (Int
rt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
recoveryLag Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Dates -> Dates) -> Dates -> Dates
forall a b. (a -> b) -> a -> b
$ Date
sdDate -> Dates -> Dates
forall a. a -> [a] -> [a]
:Installment -> Int -> Dates
forall a. Asset a => a -> Int -> Dates
getPaymentDates Installment
inst Int
recoveryLag
opmt :: Recovery
opmt = Recovery -> Int -> Recovery
divideBI Recovery
ob Int
ot
orate :: IRate
orate = Installment -> IRate
forall a. Asset a => a -> IRate
getOriginRate Installment
inst
ofee :: Recovery
ofee = Recovery -> IRate -> Recovery
mulBIR Recovery
ob IRate
orate
remainTerms :: [Int]
remainTerms = [Int] -> [Int]
forall a. [a] -> [a]
reverse ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate Int
recoveryLag Int
0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int
0..Int
rt]
scheduleBalances :: [Recovery]
scheduleBalances = (Recovery -> Recovery -> Recovery)
-> Recovery -> [Recovery] -> [Recovery]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl (-) Recovery
ob (Int -> Recovery -> [Recovery]
forall a. Int -> a -> [a]
replicate Int
ot Recovery
opmt)
currentScheduleBal :: Recovery
currentScheduleBal = [Recovery]
scheduleBalances [Recovery] -> Int -> Recovery
forall a. HasCallStack => [a] -> Int -> a
!! (Int
ot Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rt)
currentFactor :: Rational
currentFactor = Recovery -> Recovery -> Rational
divideBB Recovery
cb Recovery
currentScheduleBal
in
do
[Rational]
ppyRates <- Installment
-> Dates -> Maybe AssetPrepayAssumption -> Either String [Rational]
forall b.
Asset b =>
b
-> Dates -> Maybe AssetPrepayAssumption -> Either String [Rational]
Ast.buildPrepayRates Installment
inst (Date
lastPayDateDate -> Dates -> Dates
forall a. a -> [a] -> [a]
:Dates
cfDates) Maybe AssetPrepayAssumption
prepayAssump
[Rational]
defRates <- Installment
-> Dates
-> Maybe AssetDefaultAssumption
-> Either String [Rational]
forall b.
Asset b =>
b
-> Dates
-> Maybe AssetDefaultAssumption
-> Either String [Rational]
Ast.buildDefaultRates Installment
inst (Date
lastPayDateDate -> Dates -> Dates
forall a. a -> [a] -> [a]
:Dates
cfDates) Maybe AssetDefaultAssumption
defaultAssump
let (DList TsRow
txns,Recovery
_,Rational
_) = (Recovery, Date, (Recovery, Recovery), IRate, Rational, AmortPlan,
Int)
-> (Dates, [Rational], [Rational], [Int])
-> (DList TsRow, Recovery, Rational)
projectInstallmentFlow (Recovery
cb,Date
lastPayDate,(Recovery
opmt,Recovery
ofee),IRate
orate,Rational
currentFactor,AmortPlan
pt,Int
ot) (Dates
cfDates,[Rational]
defRates,[Rational]
ppyRates,[Int]
remainTerms)
let ([TsRow]
futureTxns,Map CutoffFields Recovery
historyM) = Date -> [TsRow] -> ([TsRow], Map CutoffFields Recovery)
CF.cutoffTrs Date
asOfDay ([TsRow] -> Maybe RecoveryAssumption -> [TsRow]
patchLossRecovery (DList TsRow -> [TsRow]
forall a. DList a -> [a]
DL.toList DList TsRow
txns) Maybe RecoveryAssumption
recoveryAssump)
let begBal :: Recovery
begBal = [TsRow] -> Recovery
CF.buildBegBal [TsRow]
futureTxns
(CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return ((CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery))
-> (CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. (a -> b) -> a -> b
$ (Maybe ExtraStress -> CashFlowFrame -> CashFlowFrame
applyHaircut Maybe ExtraStress
ams (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Recovery
begBal,Date
asOfDay,Maybe Recovery
forall a. Maybe a
Nothing) [TsRow]
futureTxns), Map CutoffFields Recovery
historyM)
projCashflow inst :: Installment
inst@(Installment (LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
ptype Maybe Obligor
_) Recovery
cb Int
rt (Defaulted (Just Date
defaultedDate)))
Date
asOfDay
(AssetPerfAssumption
_,AssetDelinqPerfAssumption
_,(A.DefaultedRecovery Rational
rr Int
lag [Rational]
timing))
Maybe [RateAssumption]
mRates
= let
(Dates
cf_dates1,Dates
cf_dates2) = Int -> Dates -> (Dates, Dates)
forall a. Int -> [a] -> ([a], [a])
splitAt Int
lag (Dates -> (Dates, Dates)) -> Dates -> (Dates, Dates)
forall a b. (a -> b) -> a -> b
$ Date -> Period -> Int -> Dates
genDates Date
defaultedDate Period
p (Int
lagInt -> Int -> Int
forall a. Num a => a -> a -> a
+[Rational] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rational]
timing)
beforeRecoveryTxn :: [TsRow]
beforeRecoveryTxn = [ Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow
CF.LoanFlow Date
d Recovery
cb Recovery
0 Recovery
0 Recovery
0 Recovery
0 Recovery
0 Recovery
0 IRate
cr Maybe CumulativeStat
forall a. Maybe a
Nothing | Date
d <- Dates
cf_dates1 ]
recoveries :: [Recovery]
recoveries = Recovery -> Rational -> [Rational] -> [Recovery]
calcRecoveriesFromDefault Recovery
cb Rational
rr [Rational]
timing
bals :: [Recovery]
bals = (Recovery -> Recovery -> Recovery)
-> Recovery -> [Recovery] -> [Recovery]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl (-) Recovery
cb [Recovery]
recoveries
_txns :: [TsRow]
_txns = [ Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow
CF.LoanFlow Date
d Recovery
b Recovery
0 Recovery
0 Recovery
0 Recovery
0 Recovery
r Recovery
0 IRate
cr Maybe CumulativeStat
forall a. Maybe a
Nothing | (Recovery
b,Date
d,Recovery
r) <- [Recovery] -> Dates -> [Recovery] -> [(Recovery, Date, Recovery)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Recovery]
bals Dates
cf_dates2 [Recovery]
recoveries ]
futureTxns :: [TsRow]
futureTxns = CutoffType -> DateDirection -> Date -> [TsRow] -> [TsRow]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Inc DateDirection
Future Date
asOfDay ([TsRow] -> [TsRow]) -> [TsRow] -> [TsRow]
forall a b. (a -> b) -> a -> b
$ [TsRow]
beforeRecoveryTxn[TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++[TsRow]
_txns
begBal :: Recovery
begBal = [TsRow] -> Recovery
CF.buildBegBal [TsRow]
futureTxns
in
(CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. b -> Either a b
Right ((CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery))
-> (CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. (a -> b) -> a -> b
$ (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Recovery
begBal,Date
asOfDay,Maybe Recovery
forall a. Maybe a
Nothing) [TsRow]
futureTxns ,Map CutoffFields Recovery
forall k a. Map k a
Map.empty)
where
cr :: IRate
cr = Installment -> IRate
forall a. Asset a => a -> IRate
getOriginRate Installment
inst
projCashflow inst :: Installment
inst@(Installment OriginalInfo
_ Recovery
cb Int
rt (Defaulted Maybe Date
Nothing)) Date
asOfDay AssetPerf
assumps Maybe [RateAssumption]
_
= (CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. b -> Either a b
Right ((CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery))
-> (CashFlowFrame, Map CutoffFields Recovery)
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. (a -> b) -> a -> b
$ (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (Recovery
cb, Date
asOfDay, Maybe Recovery
forall a. Maybe a
Nothing) ([TsRow] -> CashFlowFrame) -> [TsRow] -> CashFlowFrame
forall a b. (a -> b) -> a -> b
$ [Date
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> Recovery
-> IRate
-> Maybe CumulativeStat
-> TsRow
CF.LoanFlow Date
asOfDay Recovery
cb Recovery
0 Recovery
0 Recovery
0 Recovery
0 Recovery
0 Recovery
0 (Installment -> IRate
forall a. Asset a => a -> IRate
getOriginRate Installment
inst) Maybe CumulativeStat
forall a. Maybe a
Nothing],Map CutoffFields Recovery
forall k a. Map k a
Map.empty)
projCashflow Installment
a Date
b AssetPerf
c Maybe [RateAssumption]
d = String -> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. a -> Either a b
Left (String
-> Either String (CashFlowFrame, Map CutoffFields Recovery))
-> String
-> Either String (CashFlowFrame, Map CutoffFields Recovery)
forall a b. (a -> b) -> a -> b
$ String
"Failed to match when proj mortgage with assumption >>" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Installment -> String
forall a. Show a => a -> String
show Installment
a String -> String -> String
forall a. [a] -> [a] -> [a]
++ Date -> String
forall a. Show a => a -> String
show Date
b String -> String -> String
forall a. [a] -> [a] -> [a]
++ AssetPerf -> String
forall a. Show a => a -> String
show AssetPerf
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe [RateAssumption] -> String
forall a. Show a => a -> String
show Maybe [RateAssumption]
d
splitWith :: Installment -> [Rational] -> [Installment]
splitWith (Installment (LoanOriginalInfo Recovery
ob RateType
or Int
ot Period
p Date
sd AmortPlan
_type Maybe Obligor
_obligor) Recovery
cb Int
rt Status
st) [Rational]
rs
= [ OriginalInfo -> Recovery -> Int -> Status -> Installment
Installment (Recovery
-> RateType
-> Int
-> Period
-> Date
-> AmortPlan
-> Maybe Obligor
-> OriginalInfo
LoanOriginalInfo (Recovery -> Rational -> Recovery
mulBR Recovery
ob Rational
ratio) RateType
or Int
ot Period
p Date
sd AmortPlan
_type Maybe Obligor
_obligor) (Recovery -> Rational -> Recovery
mulBR Recovery
cb Rational
ratio) Int
rt Status
st | Rational
ratio <- [Rational]
rs ]