{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DataKinds #-}
module Cashflow (CashFlowFrame(..),Principals,Interests,Amount
,combine,mergePoolCf,sumTsCF,tsSetLoss,tsSetRecovery
,sizeCashFlowFrame,aggTsByDates,emptyCashFlowFrame
,mflowInterest,mflowPrincipal,mflowRecovery,mflowPrepayment
,mflowRental,mflowRate,sumPoolFlow,splitTrs,aggregateTsByDate
,mflowDefault,mflowLoss
,getDatesCashFlowFrame
,lookupSource,lookupSourceM,combineTss
,mflowBegBalance,tsDefaultBal
,mflowBorrowerNum,mflowPrepaymentPenalty,tsRowBalance
,emptyTsRow,mflowAmortAmount
,tsTotalCash, setPrepaymentPenalty, setPrepaymentPenaltyFlow
,getDate,getTxnLatestAsOf,totalPrincipal
,mflowWeightAverageBalance,tsDate
,totalLoss,totalDefault,totalRecovery,firstDate
,shiftCfToStartDate,cfInsertHead,buildBegTsRow,insertBegTsRow
,tsCumDefaultBal,tsCumDelinqBal,tsCumLossBal,tsCumRecoveriesBal
,TsRow(..),cfAt,cutoffTrs,patchCumulative,extendTxns,dropTailEmptyTxns
,cashflowTxn,clawbackInt,scaleTsRow,mflowFeePaid, currentCumulativeStat, patchCumulativeAtInit
,mergeCf,buildStartTsRow
,txnCumulativeStats,consolidateCashFlow, cfBeginStatus, getBegBalCashFlowFrame
,splitCashFlowFrameByDate, mergePoolCf2, buildBegBal, extendCashFlow, patchBalance
,splitPoolCashflowByDate
,getAllDatesCashFlowFrame,splitCf, cutoffCashflow
,AssetCashflow,PoolCashflow
,emptyCashflow,isEmptyRow2,appendMCashFlow
) where
import Data.Time (Day)
import Data.Fixed
import Lib (weightedBy,toDate,getIntervalFactors,daysBetween,paySeqLiabilitiesAmt)
import Util (mulBR,mulBInt,mulIR,lastOf)
import DateUtil ( splitByDate )
import Types
import qualified Data.Map as Map
import qualified Data.Time as T
import qualified Data.List as L
import Data.Maybe
import Data.Aeson hiding (json)
import Language.Haskell.TH
import GHC.Generics
import Data.Aeson.TH
import Data.Aeson.Types
import Text.Printf
import Debug.Trace
import qualified Control.Lens as Map
import Control.Applicative (liftA2)
import Data.OpenApi (HasPatch(patch), HasXml (xml))
import Control.DeepSeq (NFData,rnf)
import Data.Text.Internal.Encoding.Fusion (streamUtf16BE)
import qualified Text.Tabular as TT
import qualified Text.Tabular.AsciiArt as A
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
type Delinquent = Balance
type Amounts = [Float]
type Principals = [Principal]
type Interests = [Interest]
type Prepayments = [Prepayment]
type Recoveries = [Recovery]
type Rates = [Rate]
type CumulativeStat = (CumPrincipal,CumPrepay,CumDelinq,CumDefault,CumRecovery,CumLoss)
type AssetCashflow = CashFlowFrame
type PoolCashflow = (AssetCashflow, Maybe [AssetCashflow])
emptyCashflow :: CashFlowFrame
emptyCashflow = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame (BeginBalance
0,Date
epocDate,Maybe BeginBalance
forall a. Maybe a
Nothing) []
instance Monoid CashFlowFrame where
mempty :: CashFlowFrame
mempty = CashFlowFrame
emptyCashflow
instance Semigroup CashFlowFrame where
CashFlowFrame (BeginBalance
begBal1, Date
begDate1, Maybe BeginBalance
mAccInt1) [TsRow]
ts1 <> :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
<> CashFlowFrame (BeginBalance
begBal2, Date
begDate2, Maybe BeginBalance
mAccInt2) [TsRow]
ts2
= BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame (BeginBalance
begBal1,Date
begDate1,Maybe BeginBalance
mAccInt1) ([TsRow]
ts1 [TsRow] -> [TsRow] -> [TsRow]
forall a. Semigroup a => a -> a -> a
<> [TsRow]
ts2)
opStats :: (Balance -> Balance -> Balance) -> Maybe CumulativeStat -> Maybe CumulativeStat -> Maybe CumulativeStat
opStats :: (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe CumulativeStat
-> Maybe CumulativeStat
-> Maybe CumulativeStat
opStats BeginBalance -> BeginBalance -> BeginBalance
op (Just (BeginBalance
a1,BeginBalance
b1,BeginBalance
c1,BeginBalance
d1,BeginBalance
e1,BeginBalance
f1)) (Just (BeginBalance
a2,BeginBalance
b2,BeginBalance
c3,BeginBalance
d2,BeginBalance
e2,BeginBalance
f2)) = CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just (BeginBalance -> BeginBalance -> BeginBalance
op BeginBalance
a1 BeginBalance
a2,BeginBalance -> BeginBalance -> BeginBalance
op BeginBalance
b1 BeginBalance
b2,BeginBalance -> BeginBalance -> BeginBalance
op BeginBalance
c1 BeginBalance
c3,BeginBalance -> BeginBalance -> BeginBalance
op BeginBalance
d1 BeginBalance
d2,BeginBalance -> BeginBalance -> BeginBalance
op BeginBalance
e1 BeginBalance
e2,BeginBalance -> BeginBalance -> BeginBalance
op BeginBalance
f1 BeginBalance
f2)
opStats BeginBalance -> BeginBalance -> BeginBalance
op Maybe CumulativeStat
Nothing Maybe CumulativeStat
Nothing = Maybe CumulativeStat
forall a. Maybe a
Nothing
opStats BeginBalance -> BeginBalance -> BeginBalance
op (Just CumulativeStat
a) Maybe CumulativeStat
Nothing = CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just CumulativeStat
a
opStats BeginBalance -> BeginBalance -> BeginBalance
op Maybe CumulativeStat
Nothing (Just CumulativeStat
a) = CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just CumulativeStat
a
sumStats :: Maybe CumulativeStat -> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats :: Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
s1 Maybe CumulativeStat
s2 = (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe CumulativeStat
-> Maybe CumulativeStat
-> Maybe CumulativeStat
opStats BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) Maybe CumulativeStat
s1 Maybe CumulativeStat
s2
subStats :: Maybe CumulativeStat -> Maybe CumulativeStat -> Maybe CumulativeStat
subStats :: Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
subStats Maybe CumulativeStat
s1 Maybe CumulativeStat
s2 = (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe CumulativeStat
-> Maybe CumulativeStat
-> Maybe CumulativeStat
opStats (-) Maybe CumulativeStat
s1 Maybe CumulativeStat
s2
maxStats :: Maybe CumulativeStat -> Maybe CumulativeStat -> Maybe CumulativeStat
maxStats :: Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
maxStats Maybe CumulativeStat
s1 Maybe CumulativeStat
s2 = (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe CumulativeStat
-> Maybe CumulativeStat
-> Maybe CumulativeStat
opStats BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
max Maybe CumulativeStat
s1 Maybe CumulativeStat
s2
splitStats :: Rational -> CumulativeStat -> CumulativeStat
splitStats :: Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r st1 :: CumulativeStat
st1@(BeginBalance
a1,BeginBalance
b1,BeginBalance
c1,BeginBalance
d1,BeginBalance
e1,BeginBalance
f1) = ((BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) BeginBalance
a1,(BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) BeginBalance
b1,(BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) BeginBalance
c1,(BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) BeginBalance
d1,(BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) BeginBalance
e1,(BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) BeginBalance
f1)
type Depreciation = Balance
type NewDepreciation = Balance
type AccuredFee = Balance
type FeePaid = Balance
startOfTime :: Date
startOfTime = Integer -> Int -> Int -> Date
T.fromGregorian Integer
1900 Int
1 Int
1
data TsRow = CashFlow Date Amount
| BondFlow Date Balance Principal Interest
| MortgageFlow Date Balance Principal Interest Prepayment Default Recovery Loss IRate (Maybe BorrowerNum) (Maybe PrepaymentPenalty) (Maybe CumulativeStat)
| MortgageDelinqFlow Date Balance Principal Interest Prepayment Delinquent Default Recovery Loss IRate (Maybe BorrowerNum) (Maybe PrepaymentPenalty) (Maybe CumulativeStat)
| LoanFlow Date Balance Principal Interest Prepayment Default Recovery Loss IRate (Maybe CumulativeStat)
| LeaseFlow Date Balance Rental Default
| FixedFlow Date Balance NewDepreciation Depreciation Balance Balance
| ReceivableFlow Date Balance AccuredFee Principal FeePaid Default Recovery Loss (Maybe CumulativeStat)
deriving(Int -> TsRow -> ShowS
[TsRow] -> ShowS
TsRow -> String
(Int -> TsRow -> ShowS)
-> (TsRow -> String) -> ([TsRow] -> ShowS) -> Show TsRow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TsRow -> ShowS
showsPrec :: Int -> TsRow -> ShowS
$cshow :: TsRow -> String
show :: TsRow -> String
$cshowList :: [TsRow] -> ShowS
showList :: [TsRow] -> ShowS
Show,TsRow -> TsRow -> Bool
(TsRow -> TsRow -> Bool) -> (TsRow -> TsRow -> Bool) -> Eq TsRow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TsRow -> TsRow -> Bool
== :: TsRow -> TsRow -> Bool
$c/= :: TsRow -> TsRow -> Bool
/= :: TsRow -> TsRow -> Bool
Eq,Eq TsRow
Eq TsRow =>
(TsRow -> TsRow -> Ordering)
-> (TsRow -> TsRow -> Bool)
-> (TsRow -> TsRow -> Bool)
-> (TsRow -> TsRow -> Bool)
-> (TsRow -> TsRow -> Bool)
-> (TsRow -> TsRow -> TsRow)
-> (TsRow -> TsRow -> TsRow)
-> Ord TsRow
TsRow -> TsRow -> Bool
TsRow -> TsRow -> Ordering
TsRow -> TsRow -> TsRow
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TsRow -> TsRow -> Ordering
compare :: TsRow -> TsRow -> Ordering
$c< :: TsRow -> TsRow -> Bool
< :: TsRow -> TsRow -> Bool
$c<= :: TsRow -> TsRow -> Bool
<= :: TsRow -> TsRow -> Bool
$c> :: TsRow -> TsRow -> Bool
> :: TsRow -> TsRow -> Bool
$c>= :: TsRow -> TsRow -> Bool
>= :: TsRow -> TsRow -> Bool
$cmax :: TsRow -> TsRow -> TsRow
max :: TsRow -> TsRow -> TsRow
$cmin :: TsRow -> TsRow -> TsRow
min :: TsRow -> TsRow -> TsRow
Ord,(forall x. TsRow -> Rep TsRow x)
-> (forall x. Rep TsRow x -> TsRow) -> Generic TsRow
forall x. Rep TsRow x -> TsRow
forall x. TsRow -> Rep TsRow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TsRow -> Rep TsRow x
from :: forall x. TsRow -> Rep TsRow x
$cto :: forall x. Rep TsRow x -> TsRow
to :: forall x. Rep TsRow x -> TsRow
Generic,TsRow -> ()
(TsRow -> ()) -> NFData TsRow
forall a. (a -> ()) -> NFData a
$crnf :: TsRow -> ()
rnf :: TsRow -> ()
NFData)
instance Semigroup TsRow where
CashFlow Date
d1 BeginBalance
a1 <> :: TsRow -> TsRow -> TsRow
<> (CashFlow Date
d2 BeginBalance
a2) = Date -> BeginBalance -> TsRow
CashFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
a1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
a2)
BondFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 <> (BondFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2)
MortgageFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1 <> MortgageFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) ((Int -> Int -> Int) -> Maybe Int -> Maybe Int -> Maybe Int
forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Maybe Int
mbn1 Maybe Int
mbn2) ((BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance -> Maybe BeginBalance
forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) Maybe BeginBalance
pn1 Maybe BeginBalance
pn2) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
MortgageDelinqFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
delinq1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1 <> MortgageDelinqFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
delinq2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
delinq1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
delinq2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) ((Int -> Int -> Int) -> Maybe Int -> Maybe Int -> Maybe Int
forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Maybe Int
mbn1 Maybe Int
mbn2) ((BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance -> Maybe BeginBalance
forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) Maybe BeginBalance
pn1 Maybe BeginBalance
pn2) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
LoanFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe CumulativeStat
st1 <> LoanFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe CumulativeStat
st2
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
LeaseFlow Date
d1 BeginBalance
b1 BeginBalance
r1 BeginBalance
def1 <> LeaseFlow Date
d2 BeginBalance
b2 BeginBalance
r2 BeginBalance
def2
= Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
r1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
r2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2)
FixedFlow Date
d1 BeginBalance
b1 BeginBalance
ndep1 BeginBalance
dep1 BeginBalance
c1 BeginBalance
a1 <> FixedFlow Date
d2 BeginBalance
b2 BeginBalance
ndep2 BeginBalance
dep2 BeginBalance
c2 BeginBalance
a2
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
ndep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
ndep2) (BeginBalance
dep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
dep2) (BeginBalance
c1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c2) (BeginBalance
a1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
a2)
ReceivableFlow Date
d1 BeginBalance
b1 BeginBalance
af1 BeginBalance
p1 BeginBalance
fp1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 Maybe CumulativeStat
st1 <> ReceivableFlow Date
d2 BeginBalance
b2 BeginBalance
af2 BeginBalance
p2 BeginBalance
fp2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 Maybe CumulativeStat
st2
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
d1 Date
d2) (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
af1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
af2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
fp1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
fp2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
TsRow
a <> TsRow
b = String -> TsRow
forall a. HasCallStack => String -> a
error (String -> TsRow) -> String -> TsRow
forall a b. (a -> b) -> a -> b
$ String
"TsRow Semigroup not supported "String -> ShowS
forall a. [a] -> [a] -> [a]
++TsRow -> String
forall a. Show a => a -> String
show TsRow
aString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" "String -> ShowS
forall a. [a] -> [a] -> [a]
++TsRow -> String
forall a. Show a => a -> String
show TsRow
b
instance TimeSeries TsRow where
getDate :: TsRow -> Date
getDate (CashFlow Date
x BeginBalance
_) = Date
x
getDate (BondFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_) = Date
x
getDate (MortgageFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Date
x
getDate (MortgageDelinqFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Date
x
getDate (LoanFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = Date
x
getDate (LeaseFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_) = Date
x
getDate (FixedFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ ) = Date
x
getDate (ReceivableFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_) = Date
x
scaleTsRow :: Rational -> TsRow -> TsRow
scaleTsRow :: Rational -> TsRow -> TsRow
scaleTsRow Rational
r (CashFlow Date
d BeginBalance
a) = Date -> BeginBalance -> TsRow
CashFlow Date
d (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
a)
scaleTsRow Rational
r (BondFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
d (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
p) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
i)
scaleTsRow Rational
r (MortgageFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pp Maybe CumulativeStat
st)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
p)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
i)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
prep)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
def)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
rec)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
los)
IRate
rat
Maybe Int
mbn
Maybe BeginBalance
pp
(Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r (CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> Maybe CumulativeStat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CumulativeStat
st)
scaleTsRow Rational
r (MortgageDelinqFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
delinq BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pp Maybe CumulativeStat
st)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
p)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
i)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
prep)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
delinq)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
def)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
rec)
(Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
los)
IRate
rat
Maybe Int
mbn
Maybe BeginBalance
pp
(Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r (CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> Maybe CumulativeStat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CumulativeStat
st)
scaleTsRow Rational
r (LoanFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe CumulativeStat
st)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
p) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
i) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
prep) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
def) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
rec) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
los) IRate
rat ((Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r) (CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> Maybe CumulativeStat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CumulativeStat
st)
scaleTsRow Rational
r (LeaseFlow Date
d BeginBalance
b BeginBalance
rental BeginBalance
def) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
d (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
rental) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
def)
scaleTsRow Rational
r (FixedFlow Date
d BeginBalance
b BeginBalance
ndep BeginBalance
dep BeginBalance
c BeginBalance
a) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
d (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
ndep) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
dep) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
c) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
a)
scaleTsRow Rational
r (ReceivableFlow Date
d BeginBalance
b BeginBalance
af BeginBalance
p BeginBalance
fp BeginBalance
def BeginBalance
rec BeginBalance
los Maybe CumulativeStat
st) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
d (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
b) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
af) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
p) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
fp) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
def) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
rec) (Rational -> BeginBalance
forall a. Fractional a => Rational -> a
fromRational Rational
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
* BeginBalance
los) ((Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r) (CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> Maybe CumulativeStat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CumulativeStat
st)
type BeginBalance = Balance
type AccuredInterest = Maybe Balance
type BeginDate = Date
type BeginStatus = (BeginBalance, BeginDate, AccuredInterest)
data CashFlowFrame = CashFlowFrame BeginStatus [TsRow]
| MultiCashFlowFrame (Map.Map String [CashFlowFrame])
deriving (CashFlowFrame -> CashFlowFrame -> Bool
(CashFlowFrame -> CashFlowFrame -> Bool)
-> (CashFlowFrame -> CashFlowFrame -> Bool) -> Eq CashFlowFrame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CashFlowFrame -> CashFlowFrame -> Bool
== :: CashFlowFrame -> CashFlowFrame -> Bool
$c/= :: CashFlowFrame -> CashFlowFrame -> Bool
/= :: CashFlowFrame -> CashFlowFrame -> Bool
Eq,(forall x. CashFlowFrame -> Rep CashFlowFrame x)
-> (forall x. Rep CashFlowFrame x -> CashFlowFrame)
-> Generic CashFlowFrame
forall x. Rep CashFlowFrame x -> CashFlowFrame
forall x. CashFlowFrame -> Rep CashFlowFrame x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CashFlowFrame -> Rep CashFlowFrame x
from :: forall x. CashFlowFrame -> Rep CashFlowFrame x
$cto :: forall x. Rep CashFlowFrame x -> CashFlowFrame
to :: forall x. Rep CashFlowFrame x -> CashFlowFrame
Generic,Eq CashFlowFrame
Eq CashFlowFrame =>
(CashFlowFrame -> CashFlowFrame -> Ordering)
-> (CashFlowFrame -> CashFlowFrame -> Bool)
-> (CashFlowFrame -> CashFlowFrame -> Bool)
-> (CashFlowFrame -> CashFlowFrame -> Bool)
-> (CashFlowFrame -> CashFlowFrame -> Bool)
-> (CashFlowFrame -> CashFlowFrame -> CashFlowFrame)
-> (CashFlowFrame -> CashFlowFrame -> CashFlowFrame)
-> Ord CashFlowFrame
CashFlowFrame -> CashFlowFrame -> Bool
CashFlowFrame -> CashFlowFrame -> Ordering
CashFlowFrame -> CashFlowFrame -> CashFlowFrame
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CashFlowFrame -> CashFlowFrame -> Ordering
compare :: CashFlowFrame -> CashFlowFrame -> Ordering
$c< :: CashFlowFrame -> CashFlowFrame -> Bool
< :: CashFlowFrame -> CashFlowFrame -> Bool
$c<= :: CashFlowFrame -> CashFlowFrame -> Bool
<= :: CashFlowFrame -> CashFlowFrame -> Bool
$c> :: CashFlowFrame -> CashFlowFrame -> Bool
> :: CashFlowFrame -> CashFlowFrame -> Bool
$c>= :: CashFlowFrame -> CashFlowFrame -> Bool
>= :: CashFlowFrame -> CashFlowFrame -> Bool
$cmax :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
max :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
$cmin :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
min :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
Ord)
cfBeginStatus :: Lens' CashFlowFrame BeginStatus
cfBeginStatus :: Lens' CashFlowFrame BeginStatus
cfBeginStatus = (CashFlowFrame -> BeginStatus)
-> (CashFlowFrame -> BeginStatus -> CashFlowFrame)
-> Lens' CashFlowFrame BeginStatus
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CashFlowFrame -> BeginStatus
getter CashFlowFrame -> BeginStatus -> CashFlowFrame
setter
where
getter :: CashFlowFrame -> BeginStatus
getter (CashFlowFrame BeginStatus
st [TsRow]
_) = BeginStatus
st
setter :: CashFlowFrame -> BeginStatus -> CashFlowFrame
setter (CashFlowFrame BeginStatus
_ [TsRow]
tsRows) BeginStatus
st = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st [TsRow]
tsRows
instance Show CashFlowFrame where
show :: CashFlowFrame -> String
show (CashFlowFrame BeginStatus
st []) = String
"Empty CashflowFrame"String -> ShowS
forall a. [a] -> [a] -> [a]
++ BeginStatus -> String
forall a. Show a => a -> String
show BeginStatus
st
show (CashFlowFrame BeginStatus
st [TsRow]
txns) =
let
ds :: [String]
ds = [ Date -> String
forall a. Show a => a -> String
show Date
d | Date
d <- [TsRow] -> [Date]
forall ts. TimeSeries ts => [ts] -> [Date]
getDates [TsRow]
txns]
rowHeader :: [Header String]
rowHeader = [String -> Header String
forall h. h -> Header h
TT.Header String
h | String
h <- [String]
ds ]
getCs :: TsRow -> [String]
getCs (CashFlow {}) = [String
"Amount"]
getCs (BondFlow {}) = [String
"Balance", String
"Principal", String
"Interest"]
getCs (MortgageFlow {}) = [String
"Balance", String
"Principal", String
"Interest", String
"Prepayment", String
"Default", String
"Recovery", String
"Loss", String
"IRate", String
"BorrowerNum", String
"PrepaymentPenalty", String
"CumulativeStat"]
getCs (MortgageDelinqFlow {}) = [ String
"Balance", String
"Principal", String
"Interest", String
"Prepayment", String
"Delinquent", String
"Default", String
"Recovery", String
"Loss", String
"IRate", String
"BorrowerNum", String
"PrepaymentPenalty", String
"CumulativeStat"]
getCs (LoanFlow {}) = [String
"Balance", String
"Principal", String
"Interest", String
"Prepayment", String
"Default", String
"Recovery", String
"Loss", String
"IRate", String
"CumulativeStat"]
getCs (LeaseFlow {}) = [ String
"Balance", String
"Rental", String
"Default"]
getCs (FixedFlow {}) = [ String
"Balance", String
"NewDepreciation", String
"Depreciation", String
"Balance", String
"Amount"]
getCs (ReceivableFlow {}) = [ String
"Balance", String
"AccuredFee", String
"Principal", String
"FeePaid", String
"Default", String
"Recovery", String
"Loss", String
"CumulativeStat"]
colHeader :: [Header String]
colHeader = [String -> Header String
forall h. h -> Header h
TT.Header String
c | String
c <- TsRow -> [String]
getCs ([TsRow] -> TsRow
forall a. HasCallStack => [a] -> a
head [TsRow]
txns) ]
getRs :: TsRow -> [String]
getRs (CashFlow Date
d BeginBalance
a) = [BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
a]
getRs (BondFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
p, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
i]
getRs (MortgageFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pp Maybe CumulativeStat
st) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
p, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
i, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
prep, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
def, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
rec, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
los, IRate -> String
forall a. Show a => a -> String
show IRate
rat, Maybe Int -> String
forall a. Show a => a -> String
show Maybe Int
mbn, Maybe BeginBalance -> String
forall a. Show a => a -> String
show Maybe BeginBalance
pp, Maybe CumulativeStat -> String
forall a. Show a => a -> String
show Maybe CumulativeStat
st]
getRs (MortgageDelinqFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
delinq BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pp Maybe CumulativeStat
st) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
p, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
i, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
prep, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
delinq, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
def, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
rec, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
los, IRate -> String
forall a. Show a => a -> String
show IRate
rat, Maybe Int -> String
forall a. Show a => a -> String
show Maybe Int
mbn, Maybe BeginBalance -> String
forall a. Show a => a -> String
show Maybe BeginBalance
pp, Maybe CumulativeStat -> String
forall a. Show a => a -> String
show Maybe CumulativeStat
st]
getRs (LoanFlow Date
d BeginBalance
b BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe CumulativeStat
st) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
p, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
i, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
prep, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
def, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
rec, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
los, IRate -> String
forall a. Show a => a -> String
show IRate
rat, Maybe CumulativeStat -> String
forall a. Show a => a -> String
show Maybe CumulativeStat
st]
getRs (LeaseFlow Date
d BeginBalance
b BeginBalance
r BeginBalance
def) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
r, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
def]
getRs (FixedFlow Date
d BeginBalance
b BeginBalance
ndep BeginBalance
dep BeginBalance
c BeginBalance
a) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
ndep, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
dep, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
c, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
a]
getRs (ReceivableFlow Date
d BeginBalance
b BeginBalance
af BeginBalance
p BeginBalance
fp BeginBalance
def BeginBalance
rec BeginBalance
los Maybe CumulativeStat
st) = [ BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
b, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
af, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
p, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
fp, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
def, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
rec, BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
los, Maybe CumulativeStat -> String
forall a. Show a => a -> String
show Maybe CumulativeStat
st]
values :: [[String]]
values = [ TsRow -> [String]
getRs TsRow
txn | TsRow
txn <- [TsRow]
txns ]
tbl :: Table String String String
tbl = Header String
-> Header String -> [[String]] -> Table String String String
forall rh ch a. Header rh -> Header ch -> [[a]] -> Table rh ch a
TT.Table (Properties -> [Header String] -> Header String
forall h. Properties -> [Header h] -> Header h
TT.Group Properties
TT.SingleLine [Header String]
rowHeader) (Properties -> [Header String] -> Header String
forall h. Properties -> [Header h] -> Header h
TT.Group Properties
TT.SingleLine [Header String]
colHeader) [[String]]
values
in
BeginStatus -> String
forall a. Show a => a -> String
show BeginStatus
st String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"\n" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS -> ShowS -> ShowS -> Table String String String -> String
forall rh ch a.
(rh -> String)
-> (ch -> String) -> (a -> String) -> Table rh ch a -> String
A.render ShowS
forall a. a -> a
id ShowS
forall a. a -> a
id ShowS
forall a. a -> a
id Table String String String
tbl
instance NFData CashFlowFrame where
rnf :: CashFlowFrame -> ()
rnf (CashFlowFrame BeginStatus
st [TsRow]
txns) = BeginStatus -> ()
forall a. NFData a => a -> ()
rnf BeginStatus
st () -> () -> ()
forall a b. a -> b -> b
`seq` [TsRow] -> ()
forall a. NFData a => a -> ()
rnf [TsRow]
txns
rnf (MultiCashFlowFrame Map String [CashFlowFrame]
m) = Map String [CashFlowFrame] -> ()
forall a. NFData a => a -> ()
rnf Map String [CashFlowFrame]
m
sizeCashFlowFrame :: CashFlowFrame -> Int
sizeCashFlowFrame :: CashFlowFrame -> Int
sizeCashFlowFrame (CashFlowFrame BeginStatus
_ [TsRow]
ts) = [TsRow] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TsRow]
ts
emptyCashFlowFrame :: CashFlowFrame -> Bool
emptyCashFlowFrame :: CashFlowFrame -> Bool
emptyCashFlowFrame (CashFlowFrame BeginStatus
_ []) = Bool
True
emptyCashFlowFrame (CashFlowFrame BeginStatus
_ [TsRow]
_) = Bool
False
getDatesCashFlowFrame :: CashFlowFrame -> [Date]
getDatesCashFlowFrame :: CashFlowFrame -> [Date]
getDatesCashFlowFrame (CashFlowFrame BeginStatus
_ [TsRow]
ts) = [TsRow] -> [Date]
forall ts. TimeSeries ts => [ts] -> [Date]
getDates [TsRow]
ts
getAllDatesCashFlowFrame :: CashFlowFrame -> [Date]
getAllDatesCashFlowFrame :: CashFlowFrame -> [Date]
getAllDatesCashFlowFrame (CashFlowFrame (BeginBalance
_,Date
d,Maybe BeginBalance
_) [TsRow]
ts) = Date
d Date -> [Date] -> [Date]
forall a. a -> [a] -> [a]
: [TsRow] -> [Date]
forall ts. TimeSeries ts => [ts] -> [Date]
getDates [TsRow]
ts
getBegBalCashFlowFrame :: CashFlowFrame -> Balance
getBegBalCashFlowFrame :: CashFlowFrame -> BeginBalance
getBegBalCashFlowFrame (CashFlowFrame BeginStatus
_ []) = BeginBalance
0
getBegBalCashFlowFrame (CashFlowFrame BeginStatus
_ (TsRow
cf:[TsRow]
cfs)) = TsRow -> BeginBalance
mflowBegBalance TsRow
cf
cfAt :: CashFlowFrame -> Int -> Maybe TsRow
cfAt :: CashFlowFrame -> Int -> Maybe TsRow
cfAt (CashFlowFrame BeginStatus
_ [TsRow]
trs) Int
idx
| (Int
idx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) Bool -> Bool -> Bool
|| (Int
idx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= [TsRow] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TsRow]
trs) = Maybe TsRow
forall a. Maybe a
Nothing
| Bool
otherwise = TsRow -> Maybe TsRow
forall a. a -> Maybe a
Just ([TsRow]
trs[TsRow] -> Int -> TsRow
forall a. HasCallStack => [a] -> Int -> a
!!Int
idx)
cfInsertHead :: TsRow -> CashFlowFrame -> CashFlowFrame
cfInsertHead :: TsRow -> CashFlowFrame -> CashFlowFrame
cfInsertHead TsRow
tr (CashFlowFrame BeginStatus
st [TsRow]
trs) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st ([TsRow] -> CashFlowFrame) -> [TsRow] -> CashFlowFrame
forall a b. (a -> b) -> a -> b
$ TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
splitCashFlowFrameByDate :: CashFlowFrame -> Date -> SplitType -> (CashFlowFrame,CashFlowFrame)
splitCashFlowFrameByDate :: CashFlowFrame
-> Date -> SplitType -> (CashFlowFrame, CashFlowFrame)
splitCashFlowFrameByDate (CashFlowFrame BeginStatus
status [TsRow]
txns) Date
d SplitType
st
= let
([TsRow]
ls,[TsRow]
rs) = [TsRow] -> Date -> SplitType -> ([TsRow], [TsRow])
forall a. TimeSeries a => [a] -> Date -> SplitType -> ([a], [a])
splitByDate [TsRow]
txns Date
d SplitType
st
newStatus :: (BeginBalance, Date, Maybe a)
newStatus = case [TsRow]
rs of
[] -> (BeginBalance
0, Date
d, Maybe a
forall a. Maybe a
Nothing)
(TsRow
r:[TsRow]
_) -> ([TsRow] -> BeginBalance
buildBegBal [TsRow]
rs, Date
d, Maybe a
forall a. Maybe a
Nothing)
in
(BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
status [TsRow]
ls,BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
forall {a}. (BeginBalance, Date, Maybe a)
newStatus [TsRow]
rs)
splitPoolCashflowByDate :: PoolCashflow -> Date -> SplitType -> (PoolCashflow,PoolCashflow)
splitPoolCashflowByDate :: PoolCashflow -> Date -> SplitType -> (PoolCashflow, PoolCashflow)
splitPoolCashflowByDate (CashFlowFrame
poolCF, Maybe [CashFlowFrame]
mAssetCfs) Date
d SplitType
st
= let
(CashFlowFrame
lPoolCF,CashFlowFrame
rPoolCF) = CashFlowFrame
-> Date -> SplitType -> (CashFlowFrame, CashFlowFrame)
splitCashFlowFrameByDate CashFlowFrame
poolCF Date
d SplitType
st
mAssetSplited :: Maybe [(CashFlowFrame, CashFlowFrame)]
mAssetSplited = (\[CashFlowFrame]
xs -> [ CashFlowFrame
-> Date -> SplitType -> (CashFlowFrame, CashFlowFrame)
splitCashFlowFrameByDate CashFlowFrame
x Date
d SplitType
st | CashFlowFrame
x <- [CashFlowFrame]
xs ]) ([CashFlowFrame] -> [(CashFlowFrame, CashFlowFrame)])
-> Maybe [CashFlowFrame] -> Maybe [(CashFlowFrame, CashFlowFrame)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [CashFlowFrame]
mAssetCfs
assetCfs :: Maybe [(CashFlowFrame, CashFlowFrame)]
assetCfs = (\[(CashFlowFrame, CashFlowFrame)]
xs -> [ (CashFlowFrame
lCf, CashFlowFrame
rCf) | (CashFlowFrame
lCf,CashFlowFrame
rCf) <- [(CashFlowFrame, CashFlowFrame)]
xs ]) ([(CashFlowFrame, CashFlowFrame)]
-> [(CashFlowFrame, CashFlowFrame)])
-> Maybe [(CashFlowFrame, CashFlowFrame)]
-> Maybe [(CashFlowFrame, CashFlowFrame)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [(CashFlowFrame, CashFlowFrame)]
mAssetSplited
lAssetCfs :: Maybe [CashFlowFrame]
lAssetCfs = ((CashFlowFrame, CashFlowFrame) -> CashFlowFrame
forall a b. (a, b) -> a
fst ((CashFlowFrame, CashFlowFrame) -> CashFlowFrame)
-> [(CashFlowFrame, CashFlowFrame)] -> [CashFlowFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ([(CashFlowFrame, CashFlowFrame)] -> [CashFlowFrame])
-> Maybe [(CashFlowFrame, CashFlowFrame)] -> Maybe [CashFlowFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [(CashFlowFrame, CashFlowFrame)]
assetCfs
rAssetCfs :: Maybe [CashFlowFrame]
rAssetCfs = ((CashFlowFrame, CashFlowFrame) -> CashFlowFrame
forall a b. (a, b) -> b
snd ((CashFlowFrame, CashFlowFrame) -> CashFlowFrame)
-> [(CashFlowFrame, CashFlowFrame)] -> [CashFlowFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ([(CashFlowFrame, CashFlowFrame)] -> [CashFlowFrame])
-> Maybe [(CashFlowFrame, CashFlowFrame)] -> Maybe [CashFlowFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [(CashFlowFrame, CashFlowFrame)]
assetCfs
in
((CashFlowFrame
lPoolCF, Maybe [CashFlowFrame]
lAssetCfs) , (CashFlowFrame
rPoolCF, Maybe [CashFlowFrame]
rAssetCfs))
getTxnLatestAsOf :: CashFlowFrame -> Date -> Maybe TsRow
getTxnLatestAsOf :: CashFlowFrame -> Date -> Maybe TsRow
getTxnLatestAsOf (CashFlowFrame BeginStatus
_ [TsRow]
txn) Date
d = (TsRow -> Bool) -> [TsRow] -> Maybe TsRow
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
L.find (\TsRow
x -> TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
x Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
<= Date
d) ([TsRow] -> Maybe TsRow) -> [TsRow] -> Maybe TsRow
forall a b. (a -> b) -> a -> b
$ [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
txn
addTs :: TsRow -> TsRow -> TsRow
addTs :: TsRow -> TsRow -> TsRow
addTs (CashFlow Date
d1 BeginBalance
a1 ) (CashFlow Date
_ BeginBalance
a2 ) = Date -> BeginBalance -> TsRow
CashFlow Date
d1 (BeginBalance
a1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
a2)
addTs (BondFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 ) tr :: TsRow
tr@(BondFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 ) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2)
addTs (MortgageFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(MortgageFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2)
= let
bn :: Maybe Int
bn = Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Int -> Int -> Int) -> Maybe Int -> Maybe (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mbn1 Maybe (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mbn2
p :: Maybe BeginBalance
p = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe (BeginBalance -> BeginBalance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
pn1 Maybe (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BeginBalance
pn2
st :: Maybe CumulativeStat
st = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2
in
Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) Maybe Int
bn Maybe BeginBalance
p Maybe CumulativeStat
st
addTs (MortgageDelinqFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
delinq1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(MortgageDelinqFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
delinq2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2)
= let
bn :: Maybe Int
bn = Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Int -> Int -> Int) -> Maybe Int -> Maybe (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mbn1 Maybe (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mbn2
p :: Maybe BeginBalance
p = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe (BeginBalance -> BeginBalance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
pn1 Maybe (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BeginBalance
pn2
delinq :: BeginBalance
delinq = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) BeginBalance
delinq1 BeginBalance
delinq2
st :: Maybe CumulativeStat
st = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2
in
Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) BeginBalance
delinq (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) Maybe Int
bn Maybe BeginBalance
p Maybe CumulativeStat
st
addTs (LoanFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(LoanFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe CumulativeStat
st2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
addTs (LeaseFlow Date
d1 BeginBalance
b1 BeginBalance
r1 BeginBalance
def1) tr :: TsRow
tr@(LeaseFlow Date
d2 BeginBalance
b2 BeginBalance
r2 BeginBalance
def2)
= Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (BeginBalance
r1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
r2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2)
addTs (ReceivableFlow Date
d1 BeginBalance
b1 BeginBalance
af1 BeginBalance
p1 BeginBalance
fp1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(ReceivableFlow Date
_ BeginBalance
b2 BeginBalance
af2 BeginBalance
p2 BeginBalance
fp2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 Maybe CumulativeStat
st2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (BeginBalance
af1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
af2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
fp1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
fp2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
combineTs :: TsRow -> TsRow -> TsRow
combineTs :: TsRow -> TsRow -> TsRow
combineTs (CashFlow Date
d1 BeginBalance
a1 ) (CashFlow Date
_ BeginBalance
a2 ) = Date -> BeginBalance -> TsRow
CashFlow Date
d1 (BeginBalance
a1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
a2)
combineTs (BondFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 ) tr :: TsRow
tr@(BondFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 ) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2)
combineTs (MortgageDelinqFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
delinq1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(MortgageDelinqFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
delinq2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2)
= let
bn :: Maybe Int
bn = Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Int -> Int -> Int) -> Maybe Int -> Maybe (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mbn1 Maybe (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mbn2
p :: Maybe BeginBalance
p = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe (BeginBalance -> BeginBalance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
pn1 Maybe (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BeginBalance
pn2
delinq :: BeginBalance
delinq = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) BeginBalance
delinq1 BeginBalance
delinq2
st :: Maybe CumulativeStat
st = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2
in
Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) BeginBalance
delinq (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) Maybe Int
bn Maybe BeginBalance
p Maybe CumulativeStat
st
combineTs (MortgageFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(MortgageFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2)
= let
bn :: Maybe Int
bn = Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Int -> Int -> Int) -> Maybe Int -> Maybe (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mbn1 Maybe (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mbn2
p :: Maybe BeginBalance
p = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe (BeginBalance -> BeginBalance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
pn1 Maybe (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BeginBalance
pn2
st :: Maybe CumulativeStat
st = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2
in
Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) Maybe Int
bn Maybe BeginBalance
p Maybe CumulativeStat
st
combineTs (LoanFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(LoanFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe CumulativeStat
st2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
combineTs (LeaseFlow Date
d1 BeginBalance
b1 BeginBalance
r1 BeginBalance
def1) tr :: TsRow
tr@(LeaseFlow Date
d2 BeginBalance
b2 BeginBalance
r2 BeginBalance
def2)
= Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
r1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
r2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2)
combineTs (FixedFlow Date
d1 BeginBalance
b1 BeginBalance
de1 BeginBalance
cde1 BeginBalance
p1 BeginBalance
c1 ) (FixedFlow Date
d2 BeginBalance
b2 BeginBalance
de2 BeginBalance
cde2 BeginBalance
p2 BeginBalance
c2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
d1 (BeginBalance
b1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
b2) (BeginBalance
de1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
de2) (BeginBalance
cde1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
cde2) (BeginBalance
p1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
p2) (BeginBalance
c1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
c2)
combineTs (ReceivableFlow Date
d1 BeginBalance
b1 BeginBalance
af1 BeginBalance
p1 BeginBalance
fp1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 Maybe CumulativeStat
st1) tr :: TsRow
tr@(ReceivableFlow Date
_ BeginBalance
b2 BeginBalance
af2 BeginBalance
p2 BeginBalance
fp2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 Maybe CumulativeStat
st2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
d1 (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b2) (BeginBalance
af1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
af2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
fp1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
fp2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
combineTss :: [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss :: [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [] [] [TsRow]
r = [TsRow]
r
combineTss [] [TsRow]
r [] = [TsRow]
r
combineTss [] (TsRow
r1:[TsRow]
r1s) (TsRow
r2:[TsRow]
r2s)
| TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r1 Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
> TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r2 = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [] (TsRow
r2TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
r2s) (TsRow
r1TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
r1s)
| TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r1 Date -> Date -> Bool
forall a. Eq a => a -> a -> Bool
== TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r2 = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [TsRow -> TsRow -> TsRow
combineTs TsRow
r1 TsRow
r2] [TsRow]
r1s [TsRow]
r2s
| Bool
otherwise = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (TsRow -> BeginBalance
mflowBegBalance TsRow
r2BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+(Getting BeginBalance TsRow BeginBalance -> TsRow -> BeginBalance
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting BeginBalance TsRow BeginBalance
Lens' TsRow BeginBalance
tsRowBalance TsRow
r1)) TsRow
r1]
[TsRow]
r1s
(TsRow
r2TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
r2s)
combineTss [TsRow]
consols [] [] = [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
consols
combineTss (TsRow
consol:[TsRow]
consols) (TsRow
r:[TsRow]
rs) [] = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss (TsRow -> TsRow -> TsRow
appendTs TsRow
consol TsRow
rTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
consolTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
consols) [TsRow]
rs []
combineTss (TsRow
consol:[TsRow]
consols) [] (TsRow
tr:[TsRow]
trs) = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss (TsRow -> TsRow -> TsRow
appendTs TsRow
consol TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
consolTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
consols) [] [TsRow]
trs
combineTss (TsRow
consol:[TsRow]
consols) (TsRow
r:[TsRow]
rs) (TsRow
tr:[TsRow]
trs)
| TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r Date -> Date -> Bool
forall a. Eq a => a -> a -> Bool
== TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
tr = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss (TsRow -> TsRow -> TsRow
appendTs TsRow
consol (TsRow -> TsRow -> TsRow
combineTs TsRow
r TsRow
tr)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
consolTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
consols) [TsRow]
rs [TsRow]
trs
| TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
< TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
tr = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss (TsRow -> TsRow -> TsRow
appendTs TsRow
consol TsRow
rTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
consolTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
consols) [TsRow]
rs (TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs)
| TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
> TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
tr = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss (TsRow -> TsRow -> TsRow
appendTs TsRow
consol TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
consolTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
consols) (TsRow
rTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs) [TsRow]
trs
combineTss [TsRow]
a [TsRow]
b [TsRow]
c = String -> [TsRow]
forall a. HasCallStack => String -> a
error (String -> [TsRow]) -> String -> [TsRow]
forall a b. (a -> b) -> a -> b
$ String
"combineTss not supported "String -> ShowS
forall a. [a] -> [a] -> [a]
++[TsRow] -> String
forall a. Show a => a -> String
show [TsRow]
aString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" "String -> ShowS
forall a. [a] -> [a] -> [a]
++[TsRow] -> String
forall a. Show a => a -> String
show [TsRow]
bString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" "String -> ShowS
forall a. [a] -> [a] -> [a]
++[TsRow] -> String
forall a. Show a => a -> String
show [TsRow]
c
appendTs :: TsRow -> TsRow -> TsRow
appendTs :: TsRow -> TsRow -> TsRow
appendTs bn1 :: TsRow
bn1@(BondFlow Date
d1 BeginBalance
b1 BeginBalance
_ BeginBalance
_ ) bn2 :: TsRow
bn2@(BondFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 )
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs (MortgageDelinqFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
_ BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
_ Maybe CumulativeStat
mstat1) bn2 :: TsRow
bn2@(MortgageDelinqFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
_ BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
_ Maybe CumulativeStat
mstat2)
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs bn1 :: TsRow
bn1@(MortgageFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
_ Maybe CumulativeStat
mstat1) bn2 :: TsRow
bn2@(MortgageFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
_ Maybe CumulativeStat
mstat2)
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs (LoanFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe CumulativeStat
mstat1) bn2 :: TsRow
bn2@(LoanFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe CumulativeStat
mstat2)
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs (LeaseFlow Date
d1 BeginBalance
b1 BeginBalance
r1 BeginBalance
def1) bn2 :: TsRow
bn2@(LeaseFlow Date
d2 BeginBalance
b2 BeginBalance
r2 BeginBalance
def2)
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs (FixedFlow Date
d1 BeginBalance
b1 BeginBalance
de1 BeginBalance
cde1 BeginBalance
p1 BeginBalance
c1 ) bn2 :: TsRow
bn2@(FixedFlow Date
d2 BeginBalance
b2 BeginBalance
de2 BeginBalance
cde2 BeginBalance
p2 BeginBalance
c2)
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs (ReceivableFlow Date
d1 BeginBalance
b1 BeginBalance
af1 BeginBalance
p1 BeginBalance
fp1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 Maybe CumulativeStat
mstat1) bn2 :: TsRow
bn2@(ReceivableFlow Date
_ BeginBalance
b2 BeginBalance
af2 BeginBalance
p2 BeginBalance
fp2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 Maybe CumulativeStat
mstat2)
= ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance (BeginBalance
b1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- TsRow -> BeginBalance
mflowAmortAmount TsRow
bn2) TsRow
bn2
appendTs TsRow
_1 TsRow
_2 = String -> TsRow
forall a. HasCallStack => String -> a
error (String -> TsRow) -> String -> TsRow
forall a b. (a -> b) -> a -> b
$ String
"appendTs failed with "String -> ShowS
forall a. [a] -> [a] -> [a]
++ TsRow -> String
forall a. Show a => a -> String
show TsRow
_1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">>" String -> ShowS
forall a. [a] -> [a] -> [a]
++ TsRow -> String
forall a. Show a => a -> String
show TsRow
_2
addTsCF :: TsRow -> TsRow -> TsRow
addTsCF :: TsRow -> TsRow -> TsRow
addTsCF (CashFlow Date
d1 BeginBalance
a1 ) (CashFlow Date
_ BeginBalance
a2 ) = Date -> BeginBalance -> TsRow
CashFlow Date
d1 (BeginBalance
a1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
a2)
addTsCF (BondFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 ) (BondFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 ) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2)
addTsCF m1 :: TsRow
m1@(MortgageFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1) m2 :: TsRow
m2@(MortgageFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2)
= let
bn :: Maybe Int
bn = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int -> Int -> Int) -> Maybe Int -> Maybe (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mbn1 Maybe (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mbn2
p :: Maybe BeginBalance
p = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe (BeginBalance -> BeginBalance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
pn1 Maybe (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BeginBalance
pn2
st :: Maybe CumulativeStat
st = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
maxStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2
in
Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) Maybe Int
bn Maybe BeginBalance
p Maybe CumulativeStat
st
addTsCF (MortgageDelinqFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
delinq1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe Int
mbn1 Maybe BeginBalance
pn1 Maybe CumulativeStat
st1) (MortgageDelinqFlow Date
d2 BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
delinq2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe Int
mbn2 Maybe BeginBalance
pn2 Maybe CumulativeStat
st2)
= let
bn :: Maybe Int
bn = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int -> Int -> Int) -> Maybe Int -> Maybe (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mbn1 Maybe (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
mbn2
p :: Maybe BeginBalance
p = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) (BeginBalance -> BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe (BeginBalance -> BeginBalance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
pn1 Maybe (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BeginBalance
pn2
delinq :: BeginBalance
delinq = BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) BeginBalance
delinq1 BeginBalance
delinq2
st :: Maybe CumulativeStat
st = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
maxStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2
in
Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) BeginBalance
delinq (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) Maybe Int
bn Maybe BeginBalance
p Maybe CumulativeStat
st
addTsCF (LoanFlow Date
d1 BeginBalance
b1 BeginBalance
p1 BeginBalance
i1 BeginBalance
prep1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 IRate
rat1 Maybe CumulativeStat
st1) (LoanFlow Date
_ BeginBalance
b2 BeginBalance
p2 BeginBalance
i2 BeginBalance
prep2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 IRate
rat2 Maybe CumulativeStat
st2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
i1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
i2) (BeginBalance
prep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
prep2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
los2) (Rational -> IRate
forall a. Fractional a => Rational -> a
fromRational ([Rational] -> [Rational] -> Rational
weightedBy (BeginBalance -> Rational
forall a. Real a => a -> Rational
toRational (BeginBalance -> Rational) -> [BeginBalance] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BeginBalance
b1,BeginBalance
b2]) (IRate -> Rational
forall a. Real a => a -> Rational
toRational (IRate -> Rational) -> [IRate] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IRate
rat1,IRate
rat2]))) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
maxStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
addTsCF (LeaseFlow Date
d1 BeginBalance
b1 BeginBalance
r1 BeginBalance
def1) (LeaseFlow Date
d2 BeginBalance
b2 BeginBalance
r2 BeginBalance
def2) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
r1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
r2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2)
addTsCF (FixedFlow Date
d1 BeginBalance
b1 BeginBalance
dep1 BeginBalance
cd1 BeginBalance
u1 BeginBalance
c1) (FixedFlow Date
d2 BeginBalance
b2 BeginBalance
dep2 BeginBalance
cd2 BeginBalance
u2 BeginBalance
c2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
dep1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
dep2) (BeginBalance
cd1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
cd2) BeginBalance
u2 (BeginBalance
c1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c2)
addTsCF (ReceivableFlow Date
d1 BeginBalance
b1 BeginBalance
af1 BeginBalance
p1 BeginBalance
fp1 BeginBalance
def1 BeginBalance
rec1 BeginBalance
los1 Maybe CumulativeStat
st1) (ReceivableFlow Date
d2 BeginBalance
b2 BeginBalance
af2 BeginBalance
p2 BeginBalance
fp2 BeginBalance
def2 BeginBalance
rec2 BeginBalance
los2 Maybe CumulativeStat
st2)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
d1 (BeginBalance -> BeginBalance -> BeginBalance
forall a. Ord a => a -> a -> a
min BeginBalance
b1 BeginBalance
b2) (BeginBalance
af1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
af2) (BeginBalance
p1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p2) (BeginBalance
fp1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
fp2) (BeginBalance
def1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def2) (BeginBalance
rec1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
rec2) (BeginBalance
los1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
los2) (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
maxStats Maybe CumulativeStat
st1 Maybe CumulativeStat
st2)
buildBegBal :: [TsRow] -> Balance
buildBegBal :: [TsRow] -> BeginBalance
buildBegBal [] = BeginBalance
0
buildBegBal (TsRow
x:[TsRow]
xs) = TsRow -> BeginBalance
mflowBegBalance TsRow
x
sumTs :: [TsRow] -> Date -> TsRow
sumTs :: [TsRow] -> Date -> TsRow
sumTs [TsRow]
trs Date
d = ASetter TsRow TsRow Date Date -> Date -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow Date Date
Lens' TsRow Date
tsDate Date
d ((TsRow -> TsRow -> TsRow) -> [TsRow] -> TsRow
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 TsRow -> TsRow -> TsRow
addTs [TsRow]
trs)
sumTsCF :: [TsRow] -> Date -> TsRow
sumTsCF :: [TsRow] -> Date -> TsRow
sumTsCF [] Date
_ = String -> TsRow
forall a. HasCallStack => String -> a
error String
"sumTsCF failed with empty list"
sumTsCF [TsRow]
trs Date
d = ASetter TsRow TsRow Date Date -> Date -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow Date Date
Lens' TsRow Date
tsDate Date
d ((TsRow -> TsRow -> TsRow) -> [TsRow] -> TsRow
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 TsRow -> TsRow -> TsRow
addTsCF [TsRow]
trs)
tsTotalCash :: TsRow -> Balance
tsTotalCash :: TsRow -> BeginBalance
tsTotalCash (CashFlow Date
_ BeginBalance
x) = BeginBalance
x
tsTotalCash (BondFlow Date
_ BeginBalance
_ BeginBalance
a BeginBalance
b) = BeginBalance
a BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b
tsTotalCash (MortgageDelinqFlow Date
x BeginBalance
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
_ BeginBalance
_ BeginBalance
e BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
mPn Maybe CumulativeStat
_ ) = BeginBalance
a BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
e BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance -> Maybe BeginBalance -> BeginBalance
forall a. a -> Maybe a -> a
fromMaybe BeginBalance
0 Maybe BeginBalance
mPn
tsTotalCash (MortgageFlow Date
x BeginBalance
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
_ BeginBalance
e BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
mPn Maybe CumulativeStat
_) = BeginBalance
a BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
e BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance -> Maybe BeginBalance -> BeginBalance
forall a. a -> Maybe a -> a
fromMaybe BeginBalance
0 Maybe BeginBalance
mPn
tsTotalCash (LoanFlow Date
_ BeginBalance
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
_ BeginBalance
e BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
a BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
e
tsTotalCash (LeaseFlow Date
_ BeginBalance
_ BeginBalance
a BeginBalance
_) = BeginBalance
a
tsTotalCash (FixedFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x) = BeginBalance
x
tsTotalCash (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
a BeginBalance
b BeginBalance
_ BeginBalance
c BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance
a BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c
tsDefaultBal :: TsRow -> Either String Balance
tsDefaultBal :: TsRow -> Either String BeginBalance
tsDefaultBal CashFlow {} = String -> Either String BeginBalance
forall a b. a -> Either a b
Left String
"no default amount for bond flow"
tsDefaultBal BondFlow {} = String -> Either String BeginBalance
forall a b. a -> Either a b
Left String
"no default amount for bond flow"
tsDefaultBal (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance -> Either String BeginBalance
forall a b. b -> Either a b
Right BeginBalance
x
tsDefaultBal (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance -> Either String BeginBalance
forall a b. b -> Either a b
Right BeginBalance
x
tsDefaultBal (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance -> Either String BeginBalance
forall a b. b -> Either a b
Right BeginBalance
x
tsDefaultBal (LeaseFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
x) = BeginBalance -> Either String BeginBalance
forall a b. b -> Either a b
Right BeginBalance
x
tsDefaultBal (FixedFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_) = BeginBalance -> Either String BeginBalance
forall a b. b -> Either a b
Right BeginBalance
x
tsDefaultBal (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance -> Either String BeginBalance
forall a b. b -> Either a b
Right BeginBalance
x
tsCumulative :: Lens' TsRow (Maybe CumulativeStat)
tsCumulative :: Lens' TsRow (Maybe CumulativeStat)
tsCumulative = (TsRow -> Maybe CumulativeStat)
-> (TsRow -> Maybe CumulativeStat -> TsRow)
-> Lens' TsRow (Maybe CumulativeStat)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TsRow -> Maybe CumulativeStat
getter TsRow -> Maybe CumulativeStat -> TsRow
setter
where
getter :: TsRow -> Maybe CumulativeStat
getter (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter TsRow
_ = Maybe CumulativeStat
forall a. Maybe a
Nothing
setter :: TsRow -> Maybe CumulativeStat -> TsRow
setter (MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
_) Maybe CumulativeStat
mStat = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
mStat
setter (MortgageFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
_) Maybe CumulativeStat
mStat = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
mStat
setter (LoanFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe CumulativeStat
_) Maybe CumulativeStat
mStat = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe CumulativeStat
mStat
setter (ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
_) Maybe CumulativeStat
mStat = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
mStat
setter TsRow
x Maybe CumulativeStat
_ = TsRow
x
tsCumDefaultBal :: TsRow -> Maybe Balance
tsCumDefaultBal :: TsRow -> Maybe BeginBalance
tsCumDefaultBal TsRow
tr = Getting (First BeginBalance) TsRow BeginBalance
-> TsRow -> Maybe BeginBalance
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow
Lens' TsRow (Maybe CumulativeStat)
tsCumulative ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow)
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> Getting (First BeginBalance) TsRow BeginBalance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat
forall s t a b. Field4 s t a b => Lens s t a b
Lens CumulativeStat CumulativeStat BeginBalance BeginBalance
_4) TsRow
tr
tsCumDelinqBal :: TsRow -> Maybe Balance
tsCumDelinqBal :: TsRow -> Maybe BeginBalance
tsCumDelinqBal TsRow
tr = Getting (First BeginBalance) TsRow BeginBalance
-> TsRow -> Maybe BeginBalance
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow
Lens' TsRow (Maybe CumulativeStat)
tsCumulative ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow)
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> Getting (First BeginBalance) TsRow BeginBalance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat
forall s t a b. Field3 s t a b => Lens s t a b
Lens CumulativeStat CumulativeStat BeginBalance BeginBalance
_3) TsRow
tr
tsCumLossBal :: TsRow -> Maybe Balance
tsCumLossBal :: TsRow -> Maybe BeginBalance
tsCumLossBal TsRow
tr = Getting (First BeginBalance) TsRow BeginBalance
-> TsRow -> Maybe BeginBalance
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow
Lens' TsRow (Maybe CumulativeStat)
tsCumulative ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow)
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> Getting (First BeginBalance) TsRow BeginBalance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat
forall s t a b. Field6 s t a b => Lens s t a b
Lens CumulativeStat CumulativeStat BeginBalance BeginBalance
_6) TsRow
tr
tsCumRecoveriesBal :: TsRow -> Maybe Balance
tsCumRecoveriesBal :: TsRow -> Maybe BeginBalance
tsCumRecoveriesBal TsRow
tr = Getting (First BeginBalance) TsRow BeginBalance
-> TsRow -> Maybe BeginBalance
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow
Lens' TsRow (Maybe CumulativeStat)
tsCumulative ((Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> TsRow -> Const (First BeginBalance) TsRow)
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> Getting (First BeginBalance) TsRow BeginBalance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat))
-> ((BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat)
-> (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> Maybe CumulativeStat
-> Const (First BeginBalance) (Maybe CumulativeStat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BeginBalance -> Const (First BeginBalance) BeginBalance)
-> CumulativeStat -> Const (First BeginBalance) CumulativeStat
forall s t a b. Field5 s t a b => Lens s t a b
Lens CumulativeStat CumulativeStat BeginBalance BeginBalance
_5) TsRow
tr
tsDate :: Lens' TsRow Date
tsDate :: Lens' TsRow Date
tsDate = (TsRow -> Date) -> (TsRow -> Date -> TsRow) -> Lens' TsRow Date
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TsRow -> Date
getter TsRow -> Date -> TsRow
setter
where
getter :: TsRow -> Date
getter (CashFlow Date
x BeginBalance
_) = Date
x
getter (BondFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_) = Date
x
getter (MortgageDelinqFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Date
x
getter (MortgageFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Date
x
getter (LoanFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = Date
x
getter (LeaseFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ ) = Date
x
getter (FixedFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_) = Date
x
getter (ReceivableFlow Date
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_) = Date
x
setter :: TsRow -> Date -> TsRow
setter (CashFlow Date
_ BeginBalance
a) Date
x = Date -> BeginBalance -> TsRow
CashFlow Date
x BeginBalance
a
setter (BondFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c) Date
x = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c
setter (MortgageDelinqFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) Date
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
setter (MortgageFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k) Date
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k
setter (LoanFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i) Date
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i
setter (LeaseFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c) Date
x = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c
setter (FixedFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e) Date
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e
setter (ReceivableFlow Date
_ BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h) Date
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
x BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h
tsSetLoss :: Balance -> TsRow -> TsRow
tsSetLoss :: BeginBalance -> TsRow -> TsRow
tsSetLoss BeginBalance
x (MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
x IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
tsSetLoss BeginBalance
x (MortgageFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
x IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k
tsSetLoss BeginBalance
x (LoanFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
x IRate
h Maybe CumulativeStat
i
tsSetLoss BeginBalance
x (ReceivableFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
x Maybe CumulativeStat
h
tsSetLoss BeginBalance
x TsRow
_ = String -> TsRow
forall a. HasCallStack => String -> a
error (String -> TsRow) -> String -> TsRow
forall a b. (a -> b) -> a -> b
$ String
"Failed to set Loss for "String -> ShowS
forall a. [a] -> [a] -> [a]
++BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
x
tsSetRecovery :: Balance -> TsRow -> TsRow
tsSetRecovery :: BeginBalance -> TsRow -> TsRow
tsSetRecovery BeginBalance
x (MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
x BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
tsSetRecovery BeginBalance
x (MortgageFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
x BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k
tsSetRecovery BeginBalance
x (LoanFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
x BeginBalance
g IRate
h Maybe CumulativeStat
i
tsSetRecovery BeginBalance
x (ReceivableFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
x BeginBalance
g Maybe CumulativeStat
h
tsSetRecovery BeginBalance
x TsRow
_ = String -> TsRow
forall a. HasCallStack => String -> a
error (String -> TsRow) -> String -> TsRow
forall a b. (a -> b) -> a -> b
$ String
"Failed to set Recovery for "String -> ShowS
forall a. [a] -> [a] -> [a]
++BeginBalance -> String
forall a. Show a => a -> String
show BeginBalance
x
tsOffsetDate :: Integer -> TsRow -> TsRow
tsOffsetDate :: Integer -> TsRow -> TsRow
tsOffsetDate Integer
x (CashFlow Date
_d BeginBalance
a) = Date -> BeginBalance -> TsRow
CashFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a
tsOffsetDate Integer
x (BondFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a BeginBalance
b BeginBalance
c
tsOffsetDate Integer
x (MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
tsOffsetDate Integer
x (MortgageFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k
tsOffsetDate Integer
x (LoanFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i
tsOffsetDate Integer
x (LeaseFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a BeginBalance
b BeginBalance
c
tsOffsetDate Integer
x (ReceivableFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow (Integer -> Date -> Date
T.addDays Integer
x Date
_d) BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h
tsReduceInt :: Balance -> TsRow -> TsRow
tsReduceInt :: BeginBalance -> TsRow -> TsRow
tsReduceInt BeginBalance
x (BondFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
_d BeginBalance
a BeginBalance
b (BeginBalance
cBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
-BeginBalance
x)
tsReduceInt BeginBalance
x (MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
_d BeginBalance
a BeginBalance
b (BeginBalance
cBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
-BeginBalance
x) BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
tsReduceInt BeginBalance
x (MortgageFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
_d BeginBalance
a BeginBalance
b (BeginBalance
cBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
-BeginBalance
x) BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe Int
i Maybe BeginBalance
j Maybe CumulativeStat
k
tsReduceInt BeginBalance
x (LoanFlow Date
_d BeginBalance
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
_d BeginBalance
a BeginBalance
b (BeginBalance
cBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
-BeginBalance
x) BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g IRate
h Maybe CumulativeStat
i
tsReduceInt BeginBalance
_ TsRow
x = String -> TsRow
forall a. HasCallStack => String -> a
error (String -> TsRow) -> String -> TsRow
forall a b. (a -> b) -> a -> b
$ String
"Failed to reduce interest on asset "String -> ShowS
forall a. [a] -> [a] -> [a]
++ TsRow -> String
forall a. Show a => a -> String
show TsRow
x
clawbackInt :: Balance -> [TsRow] -> [TsRow]
clawbackInt :: BeginBalance -> [TsRow] -> [TsRow]
clawbackInt BeginBalance
bal [TsRow]
txns
= let
intFlow :: [BeginBalance]
intFlow = TsRow -> BeginBalance
mflowInterest (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
txns
intDowns :: [BeginBalance]
intDowns = BeginBalance -> [BeginBalance] -> [BeginBalance]
paySeqLiabilitiesAmt BeginBalance
bal [BeginBalance]
intFlow
in
[ BeginBalance -> TsRow -> TsRow
tsReduceInt BeginBalance
intDown TsRow
txn | (TsRow
txn,BeginBalance
intDown) <- [TsRow] -> [BeginBalance] -> [(TsRow, BeginBalance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [TsRow]
txns [BeginBalance]
intDowns]
aggregateTsByDate :: [TsRow] -> [TsRow] -> [TsRow]
aggregateTsByDate :: [TsRow] -> [TsRow] -> [TsRow]
aggregateTsByDate [TsRow]
rs [] = [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
rs
aggregateTsByDate [] (TsRow
tr:[TsRow]
trs) = [TsRow] -> [TsRow] -> [TsRow]
aggregateTsByDate [TsRow
tr] [TsRow]
trs
aggregateTsByDate (TsRow
r:[TsRow]
rs) (TsRow
tr:[TsRow]
trs)
| TsRow -> TsRow -> Bool
forall ts. TimeSeries ts => ts -> ts -> Bool
sameDate TsRow
r TsRow
tr = [TsRow] -> [TsRow] -> [TsRow]
aggregateTsByDate (TsRow -> TsRow -> TsRow
combineTs TsRow
r TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs) [TsRow]
trs
| Bool
otherwise = [TsRow] -> [TsRow] -> [TsRow]
aggregateTsByDate (TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
rTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs) [TsRow]
trs
firstDate :: CashFlowFrame -> Date
firstDate :: CashFlowFrame -> Date
firstDate (CashFlowFrame BeginStatus
_ []) = String -> Date
forall a. HasCallStack => String -> a
error String
"empty cashflow frame to get first date"
firstDate (CashFlowFrame BeginStatus
_ [TsRow
r]) = TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r
firstDate (CashFlowFrame BeginStatus
_ (TsRow
r:[TsRow]
rs)) = TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate TsRow
r
combine :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
combine :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
combine (CashFlowFrame BeginStatus
st1 []) (CashFlowFrame BeginStatus
st2 []) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st1 []
combine (CashFlowFrame BeginStatus
_ []) CashFlowFrame
cf2 = CashFlowFrame
cf2
combine CashFlowFrame
cf1 (CashFlowFrame BeginStatus
_ []) = CashFlowFrame
cf1
combine cf1 :: CashFlowFrame
cf1@(CashFlowFrame st1 :: BeginStatus
st1@(BeginBalance
begBal1,Date
begDate1,Maybe BeginBalance
acc1) [TsRow]
txn1) cf2 :: CashFlowFrame
cf2@(CashFlowFrame st2 :: BeginStatus
st2@(BeginBalance
begBal2,Date
begDate2,Maybe BeginBalance
acc2) [TsRow]
txn2)
| Date
begDate1 Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
> Date
begDate2 = CashFlowFrame -> CashFlowFrame -> CashFlowFrame
combine CashFlowFrame
cf2 CashFlowFrame
cf1
| Bool
otherwise =
let
txns :: [TsRow]
txns = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [] [TsRow]
txn1 [TsRow]
txn2
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame (BeginBalance
begBal1,Date
begDate1,Maybe BeginBalance
acc1) [TsRow]
txns
buildCollectedCF :: [[TsRow]] -> [Date] -> [TsRow] -> [[TsRow]]
buildCollectedCF :: [[TsRow]] -> [Date] -> [TsRow] -> [[TsRow]]
buildCollectedCF [] [] [] = []
buildCollectedCF [[TsRow]]
trs [] [TsRow]
_trs = [[TsRow]]
trs
buildCollectedCF [[TsRow]]
trs [Date]
ds [] = [[TsRow]]
trs [[TsRow]] -> [[TsRow]] -> [[TsRow]]
forall a. [a] -> [a] -> [a]
++ [ [Date -> TsRow -> TsRow
viewTsRow Date
_d (([TsRow] -> TsRow
forall a. HasCallStack => [a] -> a
last ([TsRow] -> TsRow) -> ([[TsRow]] -> [TsRow]) -> [[TsRow]] -> TsRow
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[TsRow]] -> [TsRow]
forall a. HasCallStack => [a] -> a
last) [[TsRow]]
trs)] | Date
_d <- [Date]
ds ]
buildCollectedCF [[TsRow]]
trs (Date
d:[Date]
ds) [TsRow]
_trs =
case [TsRow]
newFlow of
[] -> case [[TsRow]] -> ([TsRow] -> Bool) -> Maybe [TsRow]
forall a. [a] -> (a -> Bool) -> Maybe a
Util.lastOf [[TsRow]]
trs (Bool -> Bool
not (Bool -> Bool) -> ([TsRow] -> Bool) -> [TsRow] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TsRow] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) of
Maybe [TsRow]
Nothing -> [[TsRow]] -> [Date] -> [TsRow] -> [[TsRow]]
buildCollectedCF ([[TsRow]]
trs[[TsRow]] -> [[TsRow]] -> [[TsRow]]
forall a. [a] -> [a] -> [a]
++[[]]) [Date]
ds [TsRow]
_trs
Just [TsRow]
lastTr -> [[TsRow]] -> [Date] -> [TsRow] -> [[TsRow]]
buildCollectedCF ([[TsRow]]
trs[[TsRow]] -> [[TsRow]] -> [[TsRow]]
forall a. [a] -> [a] -> [a]
++[[Date -> TsRow -> TsRow
viewTsRow Date
d ([TsRow] -> TsRow
forall a. HasCallStack => [a] -> a
last [TsRow]
lastTr)]]) [Date]
ds [TsRow]
_trs
[TsRow]
newFlow -> [[TsRow]] -> [Date] -> [TsRow] -> [[TsRow]]
buildCollectedCF ([[TsRow]]
trs[[TsRow]] -> [[TsRow]] -> [[TsRow]]
forall a. [a] -> [a] -> [a]
++[[TsRow]
newFlow]) [Date]
ds [TsRow]
remains
where
([TsRow]
newFlow, [TsRow]
remains) = Date -> CutoffType -> [TsRow] -> ([TsRow], [TsRow])
forall ts.
TimeSeries ts =>
Date -> CutoffType -> [ts] -> ([ts], [ts])
splitBy Date
d CutoffType
Inc [TsRow]
_trs
buildCollectedCF [[TsRow]]
a [Date]
b [TsRow]
c = String -> [[TsRow]]
forall a. HasCallStack => String -> a
error (String -> [[TsRow]]) -> String -> [[TsRow]]
forall a b. (a -> b) -> a -> b
$ String
"buildCollectedCF failed"String -> ShowS
forall a. [a] -> [a] -> [a]
++ [[TsRow]] -> String
forall a. Show a => a -> String
show [[TsRow]]
aString -> ShowS
forall a. [a] -> [a] -> [a]
++String
">>"String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Date] -> String
forall a. Show a => a -> String
show [Date]
bString -> ShowS
forall a. [a] -> [a] -> [a]
++String
">>"String -> ShowS
forall a. [a] -> [a] -> [a]
++ [TsRow] -> String
forall a. Show a => a -> String
show [TsRow]
c
aggTsByDates :: [TsRow] -> [Date] -> [TsRow]
aggTsByDates :: [TsRow] -> [Date] -> [TsRow]
aggTsByDates [] [Date]
ds = []
aggTsByDates [TsRow]
trs [Date]
ds = ([TsRow] -> Date -> TsRow) -> ([TsRow], Date) -> TsRow
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [TsRow] -> Date -> TsRow
sumTsCF (([TsRow], Date) -> TsRow) -> [([TsRow], Date)] -> [TsRow]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (([TsRow], Date) -> Bool) -> [([TsRow], Date)] -> [([TsRow], Date)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\([TsRow]
cfs,Date
_d) -> (Bool -> Bool
not (Bool -> Bool) -> ([TsRow] -> Bool) -> [TsRow] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TsRow] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [TsRow]
cfs) ([[TsRow]] -> [Date] -> [([TsRow], Date)]
forall a b. [a] -> [b] -> [(a, b)]
zip ([[TsRow]] -> [Date] -> [TsRow] -> [[TsRow]]
buildCollectedCF [] [Date]
ds [TsRow]
trs) [Date]
ds)
mflowPrincipal :: TsRow -> Balance
mflowPrincipal :: TsRow -> BeginBalance
mflowPrincipal (BondFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
_) = BeginBalance
p
mflowPrincipal (MortgageFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrincipal (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrincipal (LoanFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrincipal (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrincipal TsRow
_ = String -> BeginBalance
forall a. HasCallStack => String -> a
error String
"not supported"
mflowInterest :: TsRow -> Balance
mflowInterest :: TsRow -> BeginBalance
mflowInterest (BondFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
i) = BeginBalance
i
mflowInterest (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowInterest (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowInterest (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowInterest TsRow
x = String -> BeginBalance
forall a. HasCallStack => String -> a
error (String -> BeginBalance) -> String -> BeginBalance
forall a b. (a -> b) -> a -> b
$ String
"not supported: getting interest from row" String -> ShowS
forall a. [a] -> [a] -> [a]
++ TsRow -> String
forall a. Show a => a -> String
show TsRow
x
mflowPrepayment :: TsRow -> Balance
mflowPrepayment :: TsRow -> BeginBalance
mflowPrepayment (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrepayment (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrepayment (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowPrepayment TsRow
_ = String -> BeginBalance
forall a. HasCallStack => String -> a
error String
"not supported"
mflowDefault :: TsRow -> Balance
mflowDefault :: TsRow -> BeginBalance
mflowDefault (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowDefault (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowDefault (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowDefault (FixedFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_) = BeginBalance
x
mflowDefault (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance
x
mflowDefault TsRow
_ = BeginBalance
0
mflowRecovery :: TsRow -> Balance
mflowRecovery :: TsRow -> BeginBalance
mflowRecovery (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowRecovery (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowRecovery (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowRecovery FixedFlow {} = BeginBalance
0
mflowRecovery (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance
x
mflowRecovery (LeaseFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_) = BeginBalance
0
mflowRecovery TsRow
_ = String -> BeginBalance
forall a. HasCallStack => String -> a
error String
"not supported"
tsRowBalance :: Lens' TsRow Balance
tsRowBalance :: Lens' TsRow BeginBalance
tsRowBalance = (TsRow -> BeginBalance)
-> (TsRow -> BeginBalance -> TsRow) -> Lens' TsRow BeginBalance
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TsRow -> BeginBalance
getter TsRow -> BeginBalance -> TsRow
setter
where
getter :: TsRow -> BeginBalance
getter (BondFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_) = BeginBalance
x
getter (MortgageFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
getter (MortgageDelinqFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
getter (LoanFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
getter (LeaseFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_) = BeginBalance
x
getter (FixedFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_) = BeginBalance
x
getter (ReceivableFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance
x
setter :: TsRow -> BeginBalance -> TsRow
setter (BondFlow Date
a BeginBalance
_ BeginBalance
p BeginBalance
i) BeginBalance
x = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
a BeginBalance
x BeginBalance
p BeginBalance
i
setter (MortgageFlow Date
a BeginBalance
_ BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pn Maybe CumulativeStat
st) BeginBalance
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
a BeginBalance
x BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pn Maybe CumulativeStat
st
setter (MortgageDelinqFlow Date
a BeginBalance
_ BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
delinq BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pn Maybe CumulativeStat
st) BeginBalance
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
a BeginBalance
x BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
delinq BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe Int
mbn Maybe BeginBalance
pn Maybe CumulativeStat
st
setter (LoanFlow Date
a BeginBalance
_ BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe CumulativeStat
st) BeginBalance
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
a BeginBalance
x BeginBalance
p BeginBalance
i BeginBalance
prep BeginBalance
def BeginBalance
rec BeginBalance
los IRate
rat Maybe CumulativeStat
st
setter (LeaseFlow Date
a BeginBalance
_ BeginBalance
r BeginBalance
def) BeginBalance
x = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
a BeginBalance
x BeginBalance
r BeginBalance
def
setter (FixedFlow Date
a BeginBalance
_ BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e) BeginBalance
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
a BeginBalance
x BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e
setter (ReceivableFlow Date
a BeginBalance
_ BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h) BeginBalance
x = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
a BeginBalance
x BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g Maybe CumulativeStat
h
mflowBegBalance :: TsRow -> Balance
mflowBegBalance :: TsRow -> BeginBalance
mflowBegBalance (BondFlow Date
_ BeginBalance
x BeginBalance
p BeginBalance
_) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p
mflowBegBalance (MortgageDelinqFlow Date
_ BeginBalance
x BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
ppy BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
delinq
mflowBegBalance (MortgageFlow Date
_ BeginBalance
x BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
def BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
ppy BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def
mflowBegBalance (LoanFlow Date
_ BeginBalance
x BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
def BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
p BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
ppy BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def
mflowBegBalance (LeaseFlow Date
_ BeginBalance
b BeginBalance
r BeginBalance
def ) = BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
r BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def
mflowBegBalance (FixedFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f ) = BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
c
mflowBegBalance (ReceivableFlow Date
_ BeginBalance
x BeginBalance
_ BeginBalance
b BeginBalance
f BeginBalance
def BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
b BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
f
mflowLoss :: TsRow -> Balance
mflowLoss :: TsRow -> BeginBalance
mflowLoss (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowLoss (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowLoss (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x IRate
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowLoss (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x Maybe CumulativeStat
_ ) = BeginBalance
x
mflowLoss TsRow
_ = BeginBalance
0
mflowDelinq :: TsRow -> Balance
mflowDelinq :: TsRow -> BeginBalance
mflowDelinq (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
x
mflowDelinq TsRow
_ = BeginBalance
0
mflowRate :: TsRow -> IRate
mflowRate :: TsRow -> IRate
mflowRate (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
x Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = IRate
x
mflowRate (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
x Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = IRate
x
mflowRate (LoanFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
x Maybe CumulativeStat
_) = IRate
x
mflowRate (BondFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_) = IRate
0
mflowRate TsRow
_ = IRate
0
mflowRental :: TsRow -> Amount
mflowRental :: TsRow -> BeginBalance
mflowRental (LeaseFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_) = BeginBalance
x
mflowRental TsRow
x = String -> BeginBalance
forall a. HasCallStack => String -> a
error (String
"not support get rental from row"String -> ShowS
forall a. [a] -> [a] -> [a]
++TsRow -> String
forall a. Show a => a -> String
show TsRow
x)
mflowFeePaid :: TsRow -> Amount
mflowFeePaid :: TsRow -> BeginBalance
mflowFeePaid (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance
x
mflowFeePaid TsRow
_ = BeginBalance
0
mflowAmortAmount :: TsRow -> Balance
mflowAmortAmount :: TsRow -> BeginBalance
mflowAmortAmount (MortgageFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
def BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
p BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
ppy BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def
mflowAmortAmount (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
delinq BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = BeginBalance
p BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
ppy BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
delinq
mflowAmortAmount (LoanFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
y BeginBalance
z BeginBalance
_ BeginBalance
_ IRate
_ Maybe CumulativeStat
_) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
y BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
z
mflowAmortAmount (LeaseFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
def) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def
mflowAmortAmount (FixedFlow Date
_ BeginBalance
_ BeginBalance
x BeginBalance
_ BeginBalance
_ BeginBalance
_) = BeginBalance
x
mflowAmortAmount (BondFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
i) = BeginBalance
p
mflowAmortAmount (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
x BeginBalance
f BeginBalance
def BeginBalance
_ BeginBalance
_ Maybe CumulativeStat
_ ) = BeginBalance
x BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
def BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
f
mflowBorrowerNum :: TsRow -> Maybe BorrowerNum
mflowBorrowerNum :: TsRow -> Maybe Int
mflowBorrowerNum (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
x Maybe BeginBalance
_ Maybe CumulativeStat
_) = Maybe Int
x
mflowBorrowerNum (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
x Maybe BeginBalance
_ Maybe CumulativeStat
_) = Maybe Int
x
mflowBorrowerNum TsRow
_ = Maybe Int
forall a. HasCallStack => a
undefined
mflowPrepaymentPenalty :: TsRow -> Balance
mflowPrepaymentPenalty :: TsRow -> BeginBalance
mflowPrepaymentPenalty (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ (Just BeginBalance
x) Maybe CumulativeStat
_) = BeginBalance
x
mflowPrepaymentPenalty (MortgageFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
Nothing Maybe CumulativeStat
_) = BeginBalance
0
mflowPrepaymentPenalty (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ (Just BeginBalance
x) Maybe CumulativeStat
_) = BeginBalance
x
mflowPrepaymentPenalty (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ BeginBalance
_ IRate
_ Maybe Int
_ Maybe BeginBalance
Nothing Maybe CumulativeStat
_) = BeginBalance
0
mflowPrepaymentPenalty TsRow
_ = BeginBalance
forall a. HasCallStack => a
undefined
mflowWeightAverageBalance :: Date -> Date -> [TsRow] -> Balance
mflowWeightAverageBalance :: Date -> Date -> [TsRow] -> BeginBalance
mflowWeightAverageBalance Date
sd Date
ed [TsRow]
trs
= [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ (BeginBalance -> Rational -> BeginBalance)
-> [BeginBalance] -> [Rational] -> [BeginBalance]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith BeginBalance -> Rational -> BeginBalance
mulBR [BeginBalance]
_bals [Rational]
_dfs
where
txns :: [TsRow]
txns = (TsRow -> Bool) -> [TsRow] -> [TsRow]
forall a. (a -> Bool) -> [a] -> [a]
filter (\TsRow
x -> (Getting Date TsRow Date -> TsRow -> Date
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Date TsRow Date
Lens' TsRow Date
tsDate TsRow
x Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
>=Date
sd)Bool -> Bool -> Bool
&& (Getting Date TsRow Date -> TsRow -> Date
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Date TsRow Date
Lens' TsRow Date
tsDate TsRow
x)Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
<=Date
ed) [TsRow]
trs
_ds :: [Date]
_ds = Getting Date TsRow Date -> TsRow -> Date
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Date TsRow Date
Lens' TsRow Date
tsDate (TsRow -> Date) -> [TsRow] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
txns
_bals :: [BeginBalance]
_bals = (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall a b. (a -> b) -> [a] -> [b]
map TsRow -> BeginBalance
mflowBegBalance [TsRow]
txns
_dfs :: [Rational]
_dfs = [Date] -> [Rational]
getIntervalFactors ([Date] -> [Rational]) -> [Date] -> [Rational]
forall a b. (a -> b) -> a -> b
$ Date
sdDate -> [Date] -> [Date]
forall a. a -> [a] -> [a]
:[Date]
_ds
emptyTsRow :: Date -> TsRow -> TsRow
emptyTsRow :: Date -> TsRow -> TsRow
emptyTsRow Date
_d (MortgageDelinqFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
0 Maybe Int
forall a. Maybe a
Nothing Maybe BeginBalance
forall a. Maybe a
Nothing Maybe CumulativeStat
forall a. Maybe a
Nothing
emptyTsRow Date
_d (MortgageFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
0 Maybe Int
forall a. Maybe a
Nothing Maybe BeginBalance
forall a. Maybe a
Nothing Maybe CumulativeStat
forall a. Maybe a
Nothing
emptyTsRow Date
_d (LoanFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
i IRate
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
0 Maybe CumulativeStat
forall a. Maybe a
Nothing
emptyTsRow Date
_d (LeaseFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0
emptyTsRow Date
_d (FixedFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f ) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0
emptyTsRow Date
_d (BondFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0
emptyTsRow Date
_d (ReceivableFlow Date
a BeginBalance
x BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
_d BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 Maybe CumulativeStat
forall a. Maybe a
Nothing
extendCashFlow :: Date -> CashFlowFrame -> CashFlowFrame
extendCashFlow :: Date -> CashFlowFrame -> CashFlowFrame
extendCashFlow Date
d (CashFlowFrame BeginStatus
st []) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st []
extendCashFlow Date
d (CashFlowFrame BeginStatus
st [TsRow]
txns)
= let
lastRow :: TsRow
lastRow = [TsRow] -> TsRow
forall a. HasCallStack => [a] -> a
last [TsRow]
txns
newTxn :: TsRow
newTxn = Date -> TsRow -> TsRow
emptyTsRow Date
d TsRow
lastRow
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st ([TsRow]
txns[TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++[TsRow
newTxn])
viewTsRow :: Date -> TsRow -> TsRow
viewTsRow :: Date -> TsRow -> TsRow
viewTsRow Date
_d (MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m
viewTsRow Date
_d (MortgageFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
viewTsRow Date
_d (LoanFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
i IRate
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
j Maybe CumulativeStat
k
viewTsRow Date
_d (LeaseFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0
viewTsRow Date
_d (FixedFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f ) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0
viewTsRow Date
_d (BondFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0
viewTsRow Date
_d (ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
_d BeginBalance
b BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 Maybe CumulativeStat
i
buildBegTsRow :: Date -> TsRow -> TsRow
buildBegTsRow :: Date -> TsRow -> TsRow
buildBegTsRow Date
d flow :: TsRow
flow@FixedFlow{} = TsRow
flow
buildBegTsRow Date
d TsRow
tr =
let
r :: TsRow
r = ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance ((Getting BeginBalance TsRow BeginBalance -> TsRow -> BeginBalance
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting BeginBalance TsRow BeginBalance
Lens' TsRow BeginBalance
tsRowBalance TsRow
tr) BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ TsRow -> BeginBalance
mflowAmortAmount TsRow
tr) (Date -> TsRow -> TsRow
emptyTsRow Date
d TsRow
tr)
rate :: IRate
rate = TsRow -> IRate
mflowRate TsRow
tr
in
IRate -> TsRow -> TsRow
tsSetRate IRate
rate TsRow
r
buildStartTsRow :: CashFlowFrame -> Maybe TsRow
buildStartTsRow :: CashFlowFrame -> Maybe TsRow
buildStartTsRow (CashFlowFrame (BeginBalance
begBal,Date
begDate,Maybe BeginBalance
accInt) []) = Maybe TsRow
forall a. Maybe a
Nothing
buildStartTsRow (CashFlowFrame (BeginBalance
begBal,Date
begDate,Maybe BeginBalance
accInt) (TsRow
txn:[TsRow]
txns)) =
let
rEmpty :: TsRow
rEmpty = Date -> TsRow -> TsRow
emptyTsRow Date
begDate TsRow
txn
r :: TsRow
r = ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance BeginBalance
begBal TsRow
rEmpty
rate :: IRate
rate = TsRow -> IRate
mflowRate TsRow
txn
in
TsRow -> Maybe TsRow
forall a. a -> Maybe a
Just (TsRow -> Maybe TsRow) -> TsRow -> Maybe TsRow
forall a b. (a -> b) -> a -> b
$ IRate -> TsRow -> TsRow
tsSetRate IRate
rate TsRow
r
tsSetRate :: IRate -> TsRow -> TsRow
tsSetRate :: IRate -> TsRow -> TsRow
tsSetRate IRate
_r (MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
_r Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m
tsSetRate IRate
_r (MortgageFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
i Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h IRate
_r Maybe Int
j Maybe BeginBalance
k Maybe CumulativeStat
l
tsSetRate IRate
_r (LoanFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
i IRate
j Maybe CumulativeStat
k) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
i IRate
_r Maybe CumulativeStat
k
tsSetRate IRate
_r (BondFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
BondFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d
tsSetRate IRate
_r (ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
i) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
i
tsSetRate IRate
_r (LeaseFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d) = Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d
tsSetRate IRate
_r (FixedFlow {} ) = String -> TsRow
forall a. HasCallStack => String -> a
error String
"Not implement set rate for FixedFlow"
tsSetRate IRate
_ TsRow
_ = String -> TsRow
forall a. HasCallStack => String -> a
error String
"Not implement set rate for this type"
insertBegTsRow :: Date -> CashFlowFrame -> CashFlowFrame
insertBegTsRow :: Date -> CashFlowFrame -> CashFlowFrame
insertBegTsRow Date
d (CashFlowFrame BeginStatus
st []) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st []
insertBegTsRow Date
d (CashFlowFrame BeginStatus
st (TsRow
txn:[TsRow]
txns))
= let
begRow :: TsRow
begRow = Date -> TsRow -> TsRow
buildBegTsRow Date
d TsRow
txn
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st (TsRow
begRowTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
txnTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
txns)
totalLoss :: CashFlowFrame -> Balance
totalLoss :: CashFlowFrame -> BeginBalance
totalLoss (CashFlowFrame BeginStatus
_ [TsRow]
rs) = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowLoss (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
rs
totalDefault :: CashFlowFrame -> Balance
totalDefault :: CashFlowFrame -> BeginBalance
totalDefault (CashFlowFrame BeginStatus
_ [TsRow]
rs) = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowDefault (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
rs
totalRecovery :: CashFlowFrame -> Balance
totalRecovery :: CashFlowFrame -> BeginBalance
totalRecovery (CashFlowFrame BeginStatus
_ [TsRow]
rs) = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowRecovery (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
rs
totalPrincipal :: CashFlowFrame -> Balance
totalPrincipal :: CashFlowFrame -> BeginBalance
totalPrincipal (CashFlowFrame BeginStatus
_ [TsRow]
rs) = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowPrincipal (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
rs
mergePoolCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf CashFlowFrame
cf (CashFlowFrame BeginStatus
_ []) = CashFlowFrame
cf
mergePoolCf (CashFlowFrame BeginStatus
_ []) CashFlowFrame
cf = CashFlowFrame
cf
mergePoolCf cf1 :: CashFlowFrame
cf1@(CashFlowFrame BeginStatus
st1 [TsRow]
txns1) cf2 :: CashFlowFrame
cf2@(CashFlowFrame BeginStatus
st2 [TsRow]
txns2)
| Date
startDate1 Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
> Date
startDate2 = CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf CashFlowFrame
cf2 CashFlowFrame
cf1
| Bool
otherwise
= let
splitDate :: Date
splitDate = CashFlowFrame -> Date
firstDate CashFlowFrame
cf2
([TsRow]
txn0,[TsRow]
txnToMerged) = [TsRow] -> Date -> SplitType -> ([TsRow], [TsRow])
forall a. TimeSeries a => [a] -> Date -> SplitType -> ([a], [a])
splitByDate [TsRow]
txns1 Date
splitDate SplitType
EqToRight
txn1 :: [TsRow]
txn1 = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [] [TsRow]
txnToMerged [TsRow]
txns2
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st1 ([TsRow]
txn0[TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++[TsRow]
txn1)
where
[Date
startDate1,Date
startDate2] = CashFlowFrame -> Date
firstDate (CashFlowFrame -> Date) -> [CashFlowFrame] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CashFlowFrame
cf1,CashFlowFrame
cf2]
aggTs :: [TsRow] -> [TsRow] -> [TsRow]
aggTs :: [TsRow] -> [TsRow] -> [TsRow]
aggTs [] [] = []
aggTs [TsRow]
rs [] = [TsRow]
rs
aggTs [] (TsRow
r:[TsRow]
rs) = [TsRow] -> [TsRow] -> [TsRow]
aggTs [TsRow
r] [TsRow]
rs
aggTs (TsRow
r:[TsRow]
rs) (TsRow
tr:[TsRow]
trs)
| TsRow -> TsRow -> Bool
forall ts. TimeSeries ts => ts -> ts -> Bool
sameDate TsRow
r TsRow
tr = [TsRow] -> [TsRow] -> [TsRow]
aggTs (TsRow -> TsRow -> TsRow
addTs TsRow
r TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs) [TsRow]
trs
| Bool
otherwise = [TsRow] -> [TsRow] -> [TsRow]
aggTs (TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:TsRow
rTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs) [TsRow]
trs
patchBalance :: (Balance,Maybe CumulativeStat) -> [TsRow] -> [TsRow] -> [TsRow]
patchBalance :: (BeginBalance, Maybe CumulativeStat)
-> [TsRow] -> [TsRow] -> [TsRow]
patchBalance (BeginBalance
bal,Maybe CumulativeStat
stat) [] [] = []
patchBalance (BeginBalance
bal,Maybe CumulativeStat
mStat) [TsRow]
r [] = case Maybe CumulativeStat
mStat of
Just CumulativeStat
stat -> CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
stat [] ([TsRow] -> [TsRow]) -> [TsRow] -> [TsRow]
forall a b. (a -> b) -> a -> b
$ [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
r
Maybe CumulativeStat
Nothing -> CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0) [] ([TsRow] -> [TsRow]) -> [TsRow] -> [TsRow]
forall a b. (a -> b) -> a -> b
$ [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
r
patchBalance (BeginBalance
bal,Maybe CumulativeStat
stat) [TsRow]
r (TsRow
tr:[TsRow]
trs) =
let
amortAmt :: BeginBalance
amortAmt = TsRow -> BeginBalance
mflowAmortAmount TsRow
tr
newBal :: BeginBalance
newBal = BeginBalance
bal BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
amortAmt
rWithUpdatedBal :: TsRow
rWithUpdatedBal = ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance BeginBalance
newBal TsRow
tr
in
(BeginBalance, Maybe CumulativeStat)
-> [TsRow] -> [TsRow] -> [TsRow]
patchBalance (BeginBalance
newBal,Maybe CumulativeStat
stat) (TsRow
rWithUpdatedBalTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
r) [TsRow]
trs
calcBeginStats :: Maybe CumulativeStat -> TsRow -> CumulativeStat
calcBeginStats :: Maybe CumulativeStat -> TsRow -> CumulativeStat
calcBeginStats Maybe CumulativeStat
Nothing TsRow
tr = (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0)
calcBeginStats (Just (BeginBalance
cumPrin,BeginBalance
cumPrepay,BeginBalance
cumDlinq,BeginBalance
cumDef,BeginBalance
cumRec,BeginBalance
cumLoss)) TsRow
tr
= case TsRow
tr of
(MortgageFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
def BeginBalance
rec BeginBalance
los IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) ->
(BeginBalance
cumPrin BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
p,BeginBalance
cumPrepay BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
ppy, BeginBalance
0 , BeginBalance
cumDef BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
def, BeginBalance
cumRec BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
rec , BeginBalance
cumLoss BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
los)
(MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
rec BeginBalance
los IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) ->
(BeginBalance
cumPrin BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
p,BeginBalance
cumPrepay BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
ppy, BeginBalance
cumDlinq BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
delinq , BeginBalance
cumDef BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
def, BeginBalance
cumRec BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
rec , BeginBalance
cumLoss BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
los)
(LoanFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
_ BeginBalance
ppy BeginBalance
def BeginBalance
rec BeginBalance
los IRate
_ Maybe CumulativeStat
_) ->
(BeginBalance
cumPrin BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
p,BeginBalance
cumPrepay BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
ppy, BeginBalance
0 , BeginBalance
cumDef BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
def, BeginBalance
cumRec BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
rec , BeginBalance
cumLoss BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
los)
(ReceivableFlow Date
_ BeginBalance
_ BeginBalance
_ BeginBalance
p BeginBalance
f BeginBalance
def BeginBalance
rec BeginBalance
los Maybe CumulativeStat
_) ->
(BeginBalance
cumPrin BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
p, BeginBalance
0 , BeginBalance
0 , BeginBalance
cumDef BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
def, BeginBalance
cumRec BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
rec , BeginBalance
cumLoss BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
los)
(BondFlow Date
_ BeginBalance
_ BeginBalance
p BeginBalance
i) ->
(BeginBalance
cumPrin BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
p,BeginBalance
0 , BeginBalance
0 , BeginBalance
0, BeginBalance
0, BeginBalance
0)
(LeaseFlow Date
_ BeginBalance
b BeginBalance
r BeginBalance
def ) ->
(BeginBalance
cumPrin BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
r,BeginBalance
0 , BeginBalance
0, BeginBalance
cumDef BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
- BeginBalance
def, BeginBalance
0, BeginBalance
0)
(FixedFlow Date
_ BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
_ ) -> (BeginBalance
0, BeginBalance
0 ,BeginBalance
0 , BeginBalance
0, BeginBalance
0, BeginBalance
0)
(CashFlow Date
_ BeginBalance
amt) -> (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0)
getCfBegStats :: CashFlowFrame -> CumulativeStat
getCfBegStats :: CashFlowFrame -> CumulativeStat
getCfBegStats (CashFlowFrame BeginStatus
_ []) = (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0)
getCfBegStats (CashFlowFrame BeginStatus
_ (TsRow
tr:[TsRow]
trs)) = Maybe CumulativeStat -> TsRow -> CumulativeStat
calcBeginStats (Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
-> TsRow -> Maybe CumulativeStat
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
Lens' TsRow (Maybe CumulativeStat)
tsCumulative TsRow
tr) TsRow
tr
mergePoolCf2 :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf2 :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf2 CashFlowFrame
cf (CashFlowFrame BeginStatus
_ []) = CashFlowFrame
cf
mergePoolCf2 (CashFlowFrame BeginStatus
_ []) CashFlowFrame
cf = CashFlowFrame
cf
mergePoolCf2 cf1 :: CashFlowFrame
cf1@(CashFlowFrame st1 :: BeginStatus
st1@(BeginBalance
bBal1,Date
bDate1,Maybe BeginBalance
a1) [TsRow]
txns1) cf2 :: CashFlowFrame
cf2@(CashFlowFrame (BeginBalance
bBal2,Date
bDate2,Maybe BeginBalance
a2) [TsRow]
txns2)
| [TsRow] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TsRow]
txns2 = ASetter CashFlowFrame CashFlowFrame [TsRow] [TsRow]
-> ([TsRow] -> [TsRow]) -> CashFlowFrame -> CashFlowFrame
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter CashFlowFrame CashFlowFrame [TsRow] [TsRow]
Lens' CashFlowFrame [TsRow]
cashflowTxn ((BeginBalance, Maybe CumulativeStat)
-> [TsRow] -> [TsRow] -> [TsRow]
patchBalance (BeginBalance
bBal1,[TsRow] -> TsRow
forall a. HasCallStack => [a] -> a
head [TsRow]
txns1 TsRow
-> Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
-> Maybe CumulativeStat
forall s a. s -> Getting a s a -> a
^. Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
Lens' TsRow (Maybe CumulativeStat)
tsCumulative) []) CashFlowFrame
cf1
| Date
bDate1 Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
> Date
bDate2 = CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf2 CashFlowFrame
cf2 CashFlowFrame
cf1
| Date
bDate1 Date -> Date -> Bool
forall a. Eq a => a -> a -> Bool
== Date
bDate2 Bool -> Bool -> Bool
&& BeginBalance
bBal2 BeginBalance -> BeginBalance -> Bool
forall a. Eq a => a -> a -> Bool
== BeginBalance
0 = CashFlowFrame
cf1
| Date
bDate1 Date -> Date -> Bool
forall a. Eq a => a -> a -> Bool
== Date
bDate2 =
let
begBal :: BeginBalance
begBal = BeginBalance
bBal1 BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+ BeginBalance
bBal2
begStat :: Maybe CumulativeStat
begStat = Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats (CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just (CashFlowFrame -> CumulativeStat
getCfBegStats CashFlowFrame
cf1)) (CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just (CashFlowFrame -> CumulativeStat
getCfBegStats CashFlowFrame
cf2))
txnsSorted :: [TsRow]
txnsSorted = [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse ([TsRow] -> [TsRow]) -> [TsRow] -> [TsRow]
forall a b. (a -> b) -> a -> b
$ (TsRow -> Date) -> [TsRow] -> [TsRow]
forall b a. Ord b => (a -> b) -> [a] -> [a]
L.sortOn TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate ([TsRow]
txns1 [TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++ [TsRow]
txns2)
txnAggregated :: [TsRow]
txnAggregated = [TsRow] -> [TsRow] -> [TsRow]
aggTs [] [TsRow]
txnsSorted
txnPatchedBalance :: [TsRow]
txnPatchedBalance = (BeginBalance, Maybe CumulativeStat)
-> [TsRow] -> [TsRow] -> [TsRow]
patchBalance (BeginBalance
begBal,Maybe CumulativeStat
begStat) [] [TsRow]
txnAggregated
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame (BeginBalance
begBal, Date
bDate1, Maybe BeginBalance
a1) [TsRow]
txnPatchedBalance
| Bool
otherwise
= let
(CashFlowFrame
resultCf1, CashFlowFrame
cfToCombine) = CashFlowFrame
-> Date -> SplitType -> (CashFlowFrame, CashFlowFrame)
splitCashFlowFrameByDate CashFlowFrame
cf1 Date
bDate2 SplitType
EqToRight
(CashFlowFrame BeginStatus
_ [TsRow]
txnCombined) = CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergePoolCf2 CashFlowFrame
cfToCombine CashFlowFrame
cf2
in
ASetter CashFlowFrame CashFlowFrame [TsRow] [TsRow]
-> ([TsRow] -> [TsRow]) -> CashFlowFrame -> CashFlowFrame
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter CashFlowFrame CashFlowFrame [TsRow] [TsRow]
Lens' CashFlowFrame [TsRow]
cashflowTxn ([TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++ [TsRow]
txnCombined) CashFlowFrame
resultCf1
mergeCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergeCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
mergeCf CashFlowFrame
cf (CashFlowFrame BeginStatus
_ []) = CashFlowFrame
cf
mergeCf (CashFlowFrame BeginStatus
_ []) CashFlowFrame
cf = CashFlowFrame
cf
mergeCf cf1 :: CashFlowFrame
cf1@(CashFlowFrame (BeginBalance
begBal1,Date
begDate1,Maybe BeginBalance
mAccInt1) [TsRow]
txns1) cf2 :: CashFlowFrame
cf2@(CashFlowFrame (BeginBalance
begBal2,Date
begDate2,Maybe BeginBalance
mAccInt2)[TsRow]
txns2)
= let
mSrow1 :: Maybe TsRow
mSrow1 = CashFlowFrame -> Maybe TsRow
buildStartTsRow CashFlowFrame
cf1
mSrow2 :: Maybe TsRow
mSrow2 = CashFlowFrame -> Maybe TsRow
buildStartTsRow CashFlowFrame
cf2
txns1' :: [TsRow]
txns1' = case Maybe TsRow
mSrow1 of
Maybe TsRow
Nothing -> [TsRow]
txns1
Just TsRow
srow1 -> TsRow
srow1TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
txns1
txns2' :: [TsRow]
txns2' = case Maybe TsRow
mSrow2 of
Maybe TsRow
Nothing -> [TsRow]
txns2
Just TsRow
srow2 -> TsRow
srow2TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
txns2
txns :: [TsRow]
txns = [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
combineTss [] [TsRow]
txns1' [TsRow]
txns2'
newSt :: BeginStatus
newSt = if Date
begDate1 Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
< Date
begDate2 then (BeginBalance
begBal1,Date
begDate1,Maybe BeginBalance
mAccInt1) else (BeginBalance
begBal2,Date
begDate2,Maybe BeginBalance
mAccInt2)
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
newSt [TsRow]
txns
consolidateCashFlow :: CashFlowFrame -> CashFlowFrame
consolidateCashFlow :: CashFlowFrame -> CashFlowFrame
consolidateCashFlow (CashFlowFrame BeginStatus
st []) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st []
consolidateCashFlow (CashFlowFrame BeginStatus
st (TsRow
txn:[TsRow]
txns))
= let
totalBals :: BeginBalance
totalBals = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowAmortAmount (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TsRow
txnTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
txns)
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st (ASetter TsRow TsRow BeginBalance BeginBalance
-> BeginBalance -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow BeginBalance BeginBalance
Lens' TsRow BeginBalance
tsRowBalance BeginBalance
totalBals TsRow
txnTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
txns)
shiftCfToStartDate :: Date -> CashFlowFrame -> CashFlowFrame
shiftCfToStartDate :: Date -> CashFlowFrame -> CashFlowFrame
shiftCfToStartDate Date
d cf :: CashFlowFrame
cf@(CashFlowFrame BeginStatus
st (TsRow
txn:[TsRow]
txns))
= let
fstDate :: Date
fstDate = CashFlowFrame -> Date
firstDate CashFlowFrame
cf
diffDays :: Integer
diffDays = Date -> Date -> Integer
daysBetween Date
fstDate Date
d
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st ([TsRow] -> CashFlowFrame) -> [TsRow] -> CashFlowFrame
forall a b. (a -> b) -> a -> b
$ Integer -> TsRow -> TsRow
tsOffsetDate Integer
diffDays (TsRow -> TsRow) -> [TsRow] -> [TsRow]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TsRow
txnTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
txns)
sumPoolFlow :: CashFlowFrame -> PoolSource -> Balance
sumPoolFlow :: CashFlowFrame -> PoolSource -> BeginBalance
sumPoolFlow (CashFlowFrame BeginStatus
_ [TsRow]
trs) PoolSource
ps
= [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ (TsRow -> PoolSource -> BeginBalance
`lookupSource` PoolSource
ps) (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
trs
lookupSource :: TsRow -> PoolSource -> Balance
lookupSource :: TsRow -> PoolSource -> BeginBalance
lookupSource TsRow
tr PoolSource
CollectedPrepayment = TsRow -> BeginBalance
mflowPrepayment TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedPrincipal = TsRow -> BeginBalance
mflowPrincipal TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedRecoveries = TsRow -> BeginBalance
mflowRecovery TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedRental = TsRow -> BeginBalance
mflowRental TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedInterest = TsRow -> BeginBalance
mflowInterest TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedPrepaymentPenalty = TsRow -> BeginBalance
mflowPrepaymentPenalty TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedFeePaid = TsRow -> BeginBalance
mflowFeePaid TsRow
tr
lookupSource TsRow
tr PoolSource
CollectedCash = TsRow -> BeginBalance
tsTotalCash TsRow
tr
lookupSource TsRow
tr PoolSource
NewDelinquencies = TsRow -> BeginBalance
mflowDelinq TsRow
tr
lookupSource TsRow
tr PoolSource
NewDefaults = TsRow -> BeginBalance
mflowDefault TsRow
tr
lookupSource TsRow
tr PoolSource
NewLosses = TsRow -> BeginBalance
mflowLoss TsRow
tr
lookupSource TsRow
tr PoolSource
CurBalance = Getting BeginBalance TsRow BeginBalance -> TsRow -> BeginBalance
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting BeginBalance TsRow BeginBalance
Lens' TsRow BeginBalance
tsRowBalance TsRow
tr
lookupSource TsRow
tr PoolSource
CurBegBalance = TsRow -> BeginBalance
mflowBegBalance TsRow
tr
lookupSource TsRow
tr PoolSource
x = String -> BeginBalance
forall a. HasCallStack => String -> a
error (String
"Failed to lookup source"String -> ShowS
forall a. [a] -> [a] -> [a]
++ PoolSource -> String
forall a. Show a => a -> String
show PoolSource
x)
lookupSourceM :: Balance -> Maybe TsRow -> PoolSource -> Balance
lookupSourceM :: BeginBalance -> Maybe TsRow -> PoolSource -> BeginBalance
lookupSourceM BeginBalance
bal Maybe TsRow
Nothing PoolSource
CurBegBalance = BeginBalance
bal
lookupSourceM BeginBalance
bal Maybe TsRow
Nothing PoolSource
CurBalance = BeginBalance
bal
lookupSourceM BeginBalance
_ Maybe TsRow
Nothing PoolSource
_ = BeginBalance
0
lookupSourceM BeginBalance
_ (Just TsRow
tr) PoolSource
ps = TsRow -> PoolSource -> BeginBalance
lookupSource TsRow
tr PoolSource
ps
setPrepaymentPenalty :: Balance -> TsRow -> TsRow
setPrepaymentPenalty :: BeginBalance -> TsRow -> TsRow
setPrepaymentPenalty BeginBalance
bal (MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k (BeginBalance -> Maybe BeginBalance
forall a. a -> Maybe a
Just BeginBalance
bal) Maybe CumulativeStat
m
setPrepaymentPenalty BeginBalance
bal (MortgageFlow Date
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k Maybe BeginBalance
l Maybe CumulativeStat
m) = Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h BeginBalance
i IRate
j Maybe Int
k (BeginBalance -> Maybe BeginBalance
forall a. a -> Maybe a
Just BeginBalance
bal) Maybe CumulativeStat
m
setPrepaymentPenalty BeginBalance
_ TsRow
_ = String -> TsRow
forall a. HasCallStack => String -> a
error String
"prepay pental only applies to MortgageFlow"
setPrepaymentPenaltyFlow :: [Balance] -> [TsRow] -> [TsRow]
setPrepaymentPenaltyFlow :: [BeginBalance] -> [TsRow] -> [TsRow]
setPrepaymentPenaltyFlow [BeginBalance]
bals [TsRow]
trs = [ BeginBalance -> TsRow -> TsRow
setPrepaymentPenalty BeginBalance
bal TsRow
tr | (BeginBalance
bal,TsRow
tr) <- [BeginBalance] -> [TsRow] -> [(BeginBalance, TsRow)]
forall a b. [a] -> [b] -> [(a, b)]
zip [BeginBalance]
bals [TsRow]
trs]
splitTs :: Rate -> TsRow -> TsRow
splitTs :: Rational -> TsRow -> TsRow
splitTs Rational
r (MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
bal Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
p Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
i Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
ppy Rational
r)
(BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
delinq Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
def Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
recovery Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
loss Rational
r)
IRate
rate ((\Int
x -> Rational -> Int
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Int -> Rational
forall a. Real a => a -> Rational
toRational Int
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
r)) (Int -> Int) -> Maybe Int -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mB) ((BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
mPPN)
(Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r (CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> Maybe CumulativeStat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CumulativeStat
mStat)
splitTs Rational
r (MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
bal Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
p Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
i Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
ppy Rational
r)
(BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
def Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
recovery Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
loss Rational
r)
IRate
rate ((\Int
x -> Rational -> Int
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Int -> Rational
forall a. Real a => a -> Rational
toRational Int
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
r)) (Int -> Int) -> Maybe Int -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
mB) ((BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
mPPN)
(Rational -> CumulativeStat -> CumulativeStat
splitStats Rational
r (CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> Maybe CumulativeStat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CumulativeStat
mStat)
splitTs Rational
r (LeaseFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
def)
= Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
d (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
bal Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
p Rational
r) (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
def Rational
r)
splitTs Rational
_ TsRow
tr = String -> TsRow
forall a. HasCallStack => String -> a
error (String -> TsRow) -> String -> TsRow
forall a b. (a -> b) -> a -> b
$ String
"Not support for spliting TsRow"String -> ShowS
forall a. [a] -> [a] -> [a]
++TsRow -> String
forall a. Show a => a -> String
show TsRow
tr
splitTrs :: Rate -> [TsRow] -> [TsRow]
splitTrs :: Rational -> [TsRow] -> [TsRow]
splitTrs Rational
r [TsRow]
trs = Rational -> TsRow -> TsRow
splitTs Rational
r (TsRow -> TsRow) -> [TsRow] -> [TsRow]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
trs
splitCf :: Rate -> CashFlowFrame -> CashFlowFrame
splitCf :: Rational -> CashFlowFrame -> CashFlowFrame
splitCf Rational
1 CashFlowFrame
cf = CashFlowFrame
cf
splitCf Rational
r (CashFlowFrame BeginStatus
st []) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st []
splitCf Rational
r (CashFlowFrame (BeginBalance
begBal, Date
begDate, Maybe BeginBalance
mAccInt) [TsRow]
trs)
= BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame (BeginBalance -> Rational -> BeginBalance
mulBR BeginBalance
begBal Rational
r, Date
begDate, (BeginBalance -> Rational -> BeginBalance
`mulBR` Rational
r) (BeginBalance -> BeginBalance)
-> Maybe BeginBalance -> Maybe BeginBalance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BeginBalance
mAccInt) ([TsRow] -> CashFlowFrame) -> [TsRow] -> CashFlowFrame
forall a b. (a -> b) -> a -> b
$ Rational -> [TsRow] -> [TsRow]
splitTrs Rational
r [TsRow]
trs
currentCumulativeStat :: [TsRow] -> CumulativeStat
currentCumulativeStat :: [TsRow] -> CumulativeStat
currentCumulativeStat [] = (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0)
currentCumulativeStat [TsRow]
trs =
let
tr :: TsRow
tr = [TsRow] -> TsRow
forall a. HasCallStack => [a] -> a
last [TsRow]
trs
in
CumulativeStat -> Maybe CumulativeStat -> CumulativeStat
forall a. a -> Maybe a -> a
fromMaybe (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0) (Maybe CumulativeStat -> CumulativeStat)
-> Maybe CumulativeStat -> CumulativeStat
forall a b. (a -> b) -> a -> b
$ Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
-> TsRow -> Maybe CumulativeStat
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
Lens' TsRow (Maybe CumulativeStat)
txnCumulativeStats TsRow
tr
cashFlowInitCumulativeStats :: Lens' CashFlowFrame (Maybe CumulativeStat)
cashFlowInitCumulativeStats :: Lens' CashFlowFrame (Maybe CumulativeStat)
cashFlowInitCumulativeStats = (CashFlowFrame -> Maybe CumulativeStat)
-> (CashFlowFrame -> Maybe CumulativeStat -> CashFlowFrame)
-> Lens' CashFlowFrame (Maybe CumulativeStat)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CashFlowFrame -> Maybe CumulativeStat
getter CashFlowFrame -> Maybe CumulativeStat -> CashFlowFrame
setter
where
getter :: CashFlowFrame -> Maybe CumulativeStat
getter (CashFlowFrame BeginStatus
_ []) = Maybe CumulativeStat
forall a. Maybe a
Nothing
getter (CashFlowFrame BeginStatus
_ (TsRow
tr:[TsRow]
trs)) = Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
-> TsRow -> Maybe CumulativeStat
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Maybe CumulativeStat) TsRow (Maybe CumulativeStat)
Lens' TsRow (Maybe CumulativeStat)
txnCumulativeStats TsRow
tr
setter :: CashFlowFrame -> Maybe CumulativeStat -> CashFlowFrame
setter (CashFlowFrame BeginStatus
st []) Maybe CumulativeStat
mStat = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st []
setter (CashFlowFrame BeginStatus
st (TsRow
tr:[TsRow]
trs)) Maybe CumulativeStat
mStat = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st ([TsRow] -> CashFlowFrame) -> [TsRow] -> CashFlowFrame
forall a b. (a -> b) -> a -> b
$ (ASetter TsRow TsRow (Maybe CumulativeStat) (Maybe CumulativeStat)
-> Maybe CumulativeStat -> TsRow -> TsRow
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter TsRow TsRow (Maybe CumulativeStat) (Maybe CumulativeStat)
Lens' TsRow (Maybe CumulativeStat)
txnCumulativeStats Maybe CumulativeStat
mStat TsRow
tr)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
patchCumulativeAtInit :: Maybe CumulativeStat -> [TsRow] -> [TsRow]
patchCumulativeAtInit :: Maybe CumulativeStat -> [TsRow] -> [TsRow]
patchCumulativeAtInit Maybe CumulativeStat
_ [] = []
patchCumulativeAtInit Maybe CumulativeStat
mStatsInit (MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat:[TsRow]
trs)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
mStat Maybe CumulativeStat
mStatsInit)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
patchCumulativeAtInit Maybe CumulativeStat
mStatsInit (MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat:[TsRow]
trs)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
mStat Maybe CumulativeStat
mStatsInit)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
patchCumulativeAtInit Maybe CumulativeStat
mStatsInit (LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe CumulativeStat
mStat:[TsRow]
trs)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
mStat Maybe CumulativeStat
mStatsInit)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
patchCumulativeAtInit Maybe CumulativeStat
mStatsInit (ReceivableFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss Maybe CumulativeStat
mStat:[TsRow]
trs)
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss (Maybe CumulativeStat
-> Maybe CumulativeStat -> Maybe CumulativeStat
sumStats Maybe CumulativeStat
mStat Maybe CumulativeStat
mStatsInit)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
patchCumulativeAtInit Maybe CumulativeStat
_ [TsRow]
trs = [TsRow]
trs
patchCumulative :: CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative :: CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
_ [TsRow]
rs [] = [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
rs
patchCumulative (BeginBalance
cPrin,BeginBalance
cPrepay,BeginBalance
cDelinq,BeginBalance
cDefault,BeginBalance
cRecovery,BeginBalance
cLoss)
[TsRow]
rs
(MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
_:[TsRow]
trs)
= CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
newSt
(Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN (CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just CumulativeStat
newSt)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs)
[TsRow]
trs
where
newSt :: CumulativeStat
newSt = (BeginBalance
cPrinBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
p,BeginBalance
cPrepayBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
ppy,BeginBalance
cDelinqBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
delinq,BeginBalance
cDefaultBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
def,BeginBalance
cRecoveryBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
recovery,BeginBalance
cLossBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
loss)
patchCumulative (BeginBalance
cPrin,BeginBalance
cPrepay,BeginBalance
cDelinq,BeginBalance
cDefault,BeginBalance
cRecovery,BeginBalance
cLoss)
[TsRow]
rs
((MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
_):[TsRow]
trs)
= CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
newSt
(Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN (CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just CumulativeStat
newSt)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs)
[TsRow]
trs
where
newSt :: CumulativeStat
newSt = (BeginBalance
cPrinBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
p,BeginBalance
cPrepayBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
ppy,BeginBalance
cDelinq,BeginBalance
cDefaultBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
def,BeginBalance
cRecoveryBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
recovery,BeginBalance
cLossBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
loss)
patchCumulative (BeginBalance
cPrin,BeginBalance
cPrepay,BeginBalance
cDelinq,BeginBalance
cDefault,BeginBalance
cRecovery,BeginBalance
cLoss)
[TsRow]
rs
((LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe CumulativeStat
_):[TsRow]
trs)
= CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
newSt
(Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate (CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just CumulativeStat
newSt)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs)
[TsRow]
trs
where
newSt :: CumulativeStat
newSt = (BeginBalance
cPrinBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
p,BeginBalance
cPrepayBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
ppy,BeginBalance
cDelinq,BeginBalance
cDefaultBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
def,BeginBalance
cRecoveryBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
recovery,BeginBalance
cLossBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
loss)
patchCumulative (BeginBalance
cPrin,BeginBalance
cPrepay,BeginBalance
cDelinq,BeginBalance
cDefault,BeginBalance
cRecovery,BeginBalance
cLoss)
[TsRow]
rs
((FixedFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f):[TsRow]
trs)
= CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
newSt
(Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> TsRow
FixedFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
fTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs)
[TsRow]
trs
where
newSt :: CumulativeStat
newSt = (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0)
patchCumulative (BeginBalance
cPrin,BeginBalance
cPrepay,BeginBalance
cDelinq,BeginBalance
cDefault,BeginBalance
cRecovery,BeginBalance
cLoss)
[TsRow]
rs
((ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h Maybe CumulativeStat
i):[TsRow]
trs)
= CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
newSt
(Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d BeginBalance
e BeginBalance
f BeginBalance
g BeginBalance
h (CumulativeStat -> Maybe CumulativeStat
forall a. a -> Maybe a
Just CumulativeStat
newSt)TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs)
[TsRow]
trs
where
newSt :: CumulativeStat
newSt = (BeginBalance
cPrinBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
c,BeginBalance
0,BeginBalance
0,BeginBalance
cDefaultBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
f,BeginBalance
cRecoveryBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
g,BeginBalance
cLossBeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
+BeginBalance
h)
patchCumulative (BeginBalance
cPrin,BeginBalance
cPrepay,BeginBalance
cDelinq,BeginBalance
cDefault,BeginBalance
cRecovery,BeginBalance
cLoss)
[TsRow]
rs
((LeaseFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
d) :[TsRow]
trs)
= CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative CumulativeStat
newSt
(Date -> BeginBalance -> BeginBalance -> BeginBalance -> TsRow
LeaseFlow Date
a BeginBalance
b BeginBalance
c BeginBalance
dTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
rs)
[TsRow]
trs
where
newSt :: CumulativeStat
newSt = (BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0,BeginBalance
0)
patchCumulative CumulativeStat
a [TsRow]
b [TsRow]
c = String -> [TsRow]
forall a. HasCallStack => String -> a
error (String
"failed to patch cumulative stats for "String -> ShowS
forall a. [a] -> [a] -> [a]
++CumulativeStat -> String
forall a. Show a => a -> String
show CumulativeStat
a String -> ShowS
forall a. [a] -> [a] -> [a]
++String
">>"String -> ShowS
forall a. [a] -> [a] -> [a]
++[TsRow] -> String
forall a. Show a => a -> String
show [TsRow]
bString -> ShowS
forall a. [a] -> [a] -> [a]
++String
">>"String -> ShowS
forall a. [a] -> [a] -> [a]
++[TsRow] -> String
forall a. Show a => a -> String
show [TsRow]
c)
cutoffTrs :: Date -> [TsRow] -> ([TsRow],Map.Map CutoffFields Balance)
cutoffTrs :: Date -> [TsRow] -> ([TsRow], Map CutoffFields BeginBalance)
cutoffTrs Date
d [] = ([],Map CutoffFields BeginBalance
forall k a. Map k a
Map.empty)
cutoffTrs Date
d [TsRow]
trs
= let
beforeTrs :: [TsRow]
beforeTrs = CutoffType -> DateDirection -> Date -> [TsRow] -> [TsRow]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Exc DateDirection
Past Date
d [TsRow]
trs
cumuDefaults :: BeginBalance
cumuDefaults = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowDefault (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
beforeTrs
cumuDelinquency :: BeginBalance
cumuDelinquency = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowDelinq (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
beforeTrs
cumuLoss :: BeginBalance
cumuLoss = [BeginBalance] -> BeginBalance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([BeginBalance] -> BeginBalance) -> [BeginBalance] -> BeginBalance
forall a b. (a -> b) -> a -> b
$ TsRow -> BeginBalance
mflowLoss (TsRow -> BeginBalance) -> [TsRow] -> [BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
beforeTrs
m :: Map CutoffFields BeginBalance
m = [(CutoffFields, BeginBalance)] -> Map CutoffFields BeginBalance
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(CutoffFields
HistoryDefaults,BeginBalance
cumuDefaults),(CutoffFields
HistoryDelinquency,BeginBalance
cumuDelinquency),(CutoffFields
HistoryLoss,BeginBalance
cumuLoss)]
afterTrs :: [TsRow]
afterTrs = CutoffType -> DateDirection -> Date -> [TsRow] -> [TsRow]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Inc DateDirection
Future Date
d [TsRow]
trs
in
(CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
patchCumulative (BeginBalance
0.0,BeginBalance
0.0,BeginBalance
0.0,BeginBalance
0.0,BeginBalance
0.0,BeginBalance
0.0) [] [TsRow]
afterTrs, Map CutoffFields BeginBalance
m)
cutoffCashflow :: Date -> Dates -> CashFlowFrame -> CashFlowFrame
cutoffCashflow :: Date -> [Date] -> CashFlowFrame -> CashFlowFrame
cutoffCashflow Date
sd [Date]
ds (CashFlowFrame BeginStatus
st []) = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st []
cutoffCashflow Date
sd [Date]
ds (CashFlowFrame BeginStatus
st [TsRow]
txns)
= let
futureTxns :: [TsRow]
futureTxns = CutoffType -> DateDirection -> Date -> [TsRow] -> [TsRow]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Inc DateDirection
Future Date
sd [TsRow]
txns
withBegTs :: [TsRow] -> [TsRow]
withBegTs [] = []
withBegTs (TsRow
tr:[TsRow]
trs) = Date -> TsRow -> TsRow
buildBegTsRow Date
sd TsRow
trTsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
: TsRow
tr TsRow -> [TsRow] -> [TsRow]
forall a. a -> [a] -> [a]
:[TsRow]
trs
aggTxns :: [TsRow]
aggTxns = [TsRow] -> [Date] -> [TsRow]
aggTsByDates ([TsRow] -> [TsRow]
withBegTs [TsRow]
futureTxns) [Date]
ds
in
BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame ([TsRow] -> BeginBalance
buildBegBal [TsRow]
aggTxns, Date
sd, Maybe BeginBalance
forall a. Maybe a
Nothing) [TsRow]
aggTxns
extendTxns :: TsRow -> [Date] -> [TsRow]
extendTxns :: TsRow -> [Date] -> [TsRow]
extendTxns TsRow
tr [Date]
ds = [ Date -> TsRow -> TsRow
emptyTsRow Date
d TsRow
tr | Date
d <- [Date]
ds ]
isEmptyRow :: TsRow -> Bool
isEmptyRow :: TsRow -> Bool
isEmptyRow (MortgageDelinqFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Bool
True
isEmptyRow (MortgageFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Bool
True
isEmptyRow (LoanFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
i Maybe CumulativeStat
j ) = Bool
True
isEmptyRow (LeaseFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0) = Bool
True
isEmptyRow (FixedFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0) = Bool
True
isEmptyRow (BondFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0) = Bool
True
isEmptyRow (CashFlow Date
_ BeginBalance
0) = Bool
True
isEmptyRow (ReceivableFlow Date
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 Maybe CumulativeStat
_ ) = Bool
True
isEmptyRow TsRow
_ = Bool
False
isEmptyRow2 :: TsRow -> Bool
isEmptyRow2 :: TsRow -> Bool
isEmptyRow2 (MortgageDelinqFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Bool
True
isEmptyRow2 (MortgageFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
_ Maybe Int
_ Maybe BeginBalance
_ Maybe CumulativeStat
_) = Bool
True
isEmptyRow2 (LoanFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 IRate
i Maybe CumulativeStat
j ) = Bool
True
isEmptyRow2 (LeaseFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
_) = Bool
True
isEmptyRow2 (FixedFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0) = Bool
True
isEmptyRow2 (BondFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
0) = Bool
True
isEmptyRow2 (CashFlow Date
_ BeginBalance
0) = Bool
True
isEmptyRow2 (ReceivableFlow Date
_ BeginBalance
_ BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 BeginBalance
0 Maybe CumulativeStat
_ ) = Bool
True
isEmptyRow2 TsRow
_ = Bool
False
dropTailEmptyTxns :: [TsRow] -> [TsRow]
dropTailEmptyTxns :: [TsRow] -> [TsRow]
dropTailEmptyTxns [TsRow]
trs
= [TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse ([TsRow] -> [TsRow]) -> [TsRow] -> [TsRow]
forall a b. (a -> b) -> a -> b
$ (TsRow -> Bool) -> [TsRow] -> [TsRow]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile TsRow -> Bool
isEmptyRow ([TsRow] -> [TsRow]
forall a. [a] -> [a]
reverse [TsRow]
trs)
cashflowTxn :: Lens' CashFlowFrame [TsRow]
cashflowTxn :: Lens' CashFlowFrame [TsRow]
cashflowTxn = (CashFlowFrame -> [TsRow])
-> (CashFlowFrame -> [TsRow] -> CashFlowFrame)
-> Lens' CashFlowFrame [TsRow]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens CashFlowFrame -> [TsRow]
getter CashFlowFrame -> [TsRow] -> CashFlowFrame
setter
where
getter :: CashFlowFrame -> [TsRow]
getter (CashFlowFrame BeginStatus
_ [TsRow]
txns) = [TsRow]
txns
setter :: CashFlowFrame -> [TsRow] -> CashFlowFrame
setter (CashFlowFrame BeginStatus
st [TsRow]
txns) [TsRow]
newTxns = BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st [TsRow]
newTxns
appendMCashFlow :: Maybe CashFlowFrame -> [TsRow] -> Maybe CashFlowFrame
appendMCashFlow :: Maybe CashFlowFrame -> [TsRow] -> Maybe CashFlowFrame
appendMCashFlow Maybe CashFlowFrame
Nothing [] = Maybe CashFlowFrame
forall a. Maybe a
Nothing
appendMCashFlow (Just CashFlowFrame
cf) [] = CashFlowFrame -> Maybe CashFlowFrame
forall a. a -> Maybe a
Just CashFlowFrame
cf
appendMCashFlow Maybe CashFlowFrame
Nothing [TsRow]
txns
= CashFlowFrame -> Maybe CashFlowFrame
forall a. a -> Maybe a
Just (CashFlowFrame -> Maybe CashFlowFrame)
-> CashFlowFrame -> Maybe CashFlowFrame
forall a b. (a -> b) -> a -> b
$ BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame (BeginBalance
0, Date
epocDate, Maybe BeginBalance
forall a. Maybe a
Nothing) [TsRow]
txns
appendMCashFlow (Just (CashFlowFrame BeginStatus
st [TsRow]
txns)) [TsRow]
newTxns
= CashFlowFrame -> Maybe CashFlowFrame
forall a. a -> Maybe a
Just (CashFlowFrame -> Maybe CashFlowFrame)
-> CashFlowFrame -> Maybe CashFlowFrame
forall a b. (a -> b) -> a -> b
$ BeginStatus -> [TsRow] -> CashFlowFrame
CashFlowFrame BeginStatus
st ([TsRow]
txns [TsRow] -> [TsRow] -> [TsRow]
forall a. [a] -> [a] -> [a]
++ [TsRow]
newTxns)
txnCumulativeStats :: Lens' TsRow (Maybe CumulativeStat)
txnCumulativeStats :: Lens' TsRow (Maybe CumulativeStat)
txnCumulativeStats = (TsRow -> Maybe CumulativeStat)
-> (TsRow -> Maybe CumulativeStat -> TsRow)
-> Lens' TsRow (Maybe CumulativeStat)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TsRow -> Maybe CumulativeStat
getter TsRow -> Maybe CumulativeStat -> TsRow
setter
where
getter :: TsRow -> Maybe CumulativeStat
getter (MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter (MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter (LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter (ReceivableFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss Maybe CumulativeStat
mStat) = Maybe CumulativeStat
mStat
getter TsRow
_ = Maybe CumulativeStat
forall a. Maybe a
Nothing
setter :: TsRow -> Maybe CumulativeStat -> TsRow
setter (MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
_) Maybe CumulativeStat
mStat
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageDelinqFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
delinq BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat
setter (MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
_) Maybe CumulativeStat
mStat
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe Int
-> Maybe BeginBalance
-> Maybe CumulativeStat
-> TsRow
MortgageFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe Int
mB Maybe BeginBalance
mPPN Maybe CumulativeStat
mStat
setter (LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe CumulativeStat
_) Maybe CumulativeStat
mStat
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> IRate
-> Maybe CumulativeStat
-> TsRow
LoanFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss IRate
rate Maybe CumulativeStat
mStat
setter (ReceivableFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss Maybe CumulativeStat
_) Maybe CumulativeStat
mStat
= Date
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> BeginBalance
-> Maybe CumulativeStat
-> TsRow
ReceivableFlow Date
d BeginBalance
bal BeginBalance
p BeginBalance
i BeginBalance
ppy BeginBalance
def BeginBalance
recovery BeginBalance
loss Maybe CumulativeStat
mStat
setter TsRow
x Maybe CumulativeStat
_ = TsRow
x
$(deriveJSON defaultOptions ''TsRow)
$(deriveJSON defaultOptions ''CashFlowFrame)