{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
module Asset ( Asset(..),
buildAssumptionPpyDefRecRate,buildAssumptionPpyDelinqDefRecRate
,calcRecoveriesFromDefault,getCurBalance
,priceAsset,applyHaircut,buildPrepayRates,buildDefaultRates,getObligorFields
,getObligorTags,getObligorId,getRecoveryLagAndRate,getDefaultDelinqAssump,getOriginInfo
) where
import qualified Data.Time as T
import qualified Data.Text as Text
import Text.Read (readMaybe)
import Lib (Period(..)
,Ts(..),periodRateFromAnnualRate,toDate
,getIntervalDays,zipWith9,mkTs,periodsBetween
,mkRateTs,daysBetween, getIntervalFactors)
import qualified Cashflow as CF
import qualified Assumptions as A
import qualified AssetClass.AssetBase as ACM
import AssetClass.AssetCashflow
import qualified Data.Map as Map
import Analytics
import Data.List
import Data.Maybe
import Data.Ratio
import Data.Aeson hiding (json)
import Language.Haskell.TH
import GHC.Generics
import Data.Aeson.TH
import Data.Aeson.Types
import Types hiding (Current)
import Text.Printf
import Data.Fixed
import qualified InterestRate as IR
import qualified Data.Set as Set
import Util
import AssetClass.AssetBase ( OriginalInfo(..), calcPmt, AssetUnion, Obligor(..) )
import Debug.Trace
import Assumptions (ExtraStress(ExtraStress))
import Control.Lens hiding (element)
import Control.Lens.TH
import Data.Generics.Product.Fields
import Data.Generics.Product.Any
import DateUtil (yearCountFraction)
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
class (Show a,IR.UseRate a) => Asset a where
calcCashflow :: a -> Date -> Maybe [RateAssumption] -> Either String CF.CashFlowFrame
getCurrentBal :: a -> Balance
getOriginBal :: a -> Balance
getOriginRate :: a -> IRate
getCurrentRate :: a -> IRate
getOriginDate :: a -> Date
getOriginInfo :: a -> OriginalInfo
isDefaulted :: a -> Bool
getPaymentDates :: a -> Int -> [Date]
getRemainTerms :: a -> Int
getRemainDates :: a -> [Date]
getRemainDates a
a = Int -> [Date] -> [Date]
forall a. Int -> [a] -> [a]
lastN (a -> Int
forall a. Asset a => a -> Int
getRemainTerms a
a) (a -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
getPaymentDates a
a Int
0)
getTotalTerms :: a -> Int
getTotalTerms a
a = OriginalInfo -> Int
ACM.originTerm (a -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo a
a)
getPastTerms :: a -> Int
getPastTerms a
a = a -> Int
forall a. Asset a => a -> Int
getTotalTerms a
a Int -> Int -> Int
forall a. Num a => a -> a -> a
- a -> Int
forall a. Asset a => a -> Int
getRemainTerms a
a
projCashflow :: a -> Date -> A.AssetPerf -> Maybe [RateAssumption] -> Either String (CF.CashFlowFrame, Map.Map CutoffFields Balance)
getBorrowerNum :: a -> Int
splitWith :: a -> [Rate] -> [a]
updateOriginDate :: a -> Date -> a
resetToOrig :: a -> a
getLastInterestPaymentDate :: a -> Maybe Date
calcAccruedInterest :: a -> Date -> Balance
calcAlignDate :: a -> Date -> Date
calcAlignDate a
ast Date
d = let
payDates :: [Date]
payDates = a -> Date
forall a. Asset a => a -> Date
Asset.getOriginDate a
astDate -> [Date] -> [Date]
forall a. a -> [a] -> [a]
:a -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
getPaymentDates a
ast Int
0
remainTerms :: Int
remainTerms = a -> Int
forall a. Asset a => a -> Int
getRemainTerms a
ast
benchDate :: Date
benchDate = [Date] -> [Date]
forall a. [a] -> [a]
reverse [Date]
payDates[Date] -> Int -> Date
forall a. HasCallStack => [a] -> Int -> a
!! Int
remainTerms
offset :: Integer
offset = Date -> Date -> Integer
daysBetween Date
benchDate Date
d
in
Integer -> Date -> Date
T.addDays Integer
offset (Date -> Date) -> Date -> Date
forall a b. (a -> b) -> a -> b
$ a -> Date
forall a. Asset a => a -> Date
Asset.getOriginDate a
ast
getObligor :: a -> Maybe Obligor
getObligor a
a =
case a -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo a
a of
FixedAssetInfo {} -> Maybe Obligor
forall a. Maybe a
Nothing
MortgageOriginalInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Maybe Obligor
x } -> Maybe Obligor
x
LoanOriginalInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Maybe Obligor
x } -> Maybe Obligor
x
LeaseInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Maybe Obligor
x } -> Maybe Obligor
x
ReceivableInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Maybe Obligor
x } -> Maybe Obligor
x
getObligorTags :: a -> Set.Set String
getObligorTags a
a =
case a -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo a
a of
MortgageOriginalInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList (Obligor -> [String]
obligorTag Obligor
obr)
LoanOriginalInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList (Obligor -> [String]
obligorTag Obligor
obr)
LeaseInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList (Obligor -> [String]
obligorTag Obligor
obr)
ReceivableInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList (Obligor -> [String]
obligorTag Obligor
obr)
OriginalInfo
_ -> Set String
forall a. Monoid a => a
mempty
getObligorId :: a -> Maybe String
getObligorId a
a =
case a -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo a
a of
MortgageOriginalInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> String -> Maybe String
forall a. a -> Maybe a
Just (Obligor -> String
obligorId Obligor
obr)
LoanOriginalInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> String -> Maybe String
forall a. a -> Maybe a
Just (Obligor -> String
obligorId Obligor
obr)
LeaseInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> String -> Maybe String
forall a. a -> Maybe a
Just (Obligor -> String
obligorId Obligor
obr)
ReceivableInfo{obligor :: OriginalInfo -> Maybe Obligor
obligor = Just Obligor
obr } -> String -> Maybe String
forall a. a -> Maybe a
Just (Obligor -> String
obligorId Obligor
obr)
OriginalInfo
_ -> Maybe String
forall a. Maybe a
Nothing
getObligorFields :: a -> Maybe (Map.Map String (Either String Double))
getObligorFields a
a =
let
obInfo :: Maybe Obligor
obInfo = a -> Maybe Obligor
forall a. Asset a => a -> Maybe Obligor
getObligor a
a
in
case Maybe Obligor
obInfo of
Maybe Obligor
Nothing -> Maybe (Map String (Either String Double))
forall a. Maybe a
Nothing
Just Obligor
ob -> Map String (Either String Double)
-> Maybe (Map String (Either String Double))
forall a. a -> Maybe a
Just (Obligor -> Map String (Either String Double)
obligorFields Obligor
ob)
{-# MINIMAL calcCashflow,getCurrentBal,getOriginBal,getOriginRate #-}
applyExtraStress :: Maybe A.ExtraStress -> [Date] -> [Rate] -> [Rate] -> ([Rate],[Rate])
Maybe ExtraStress
Nothing [Date]
_ [Rate]
ppy [Rate]
def = ([Rate]
ppy,[Rate]
def)
applyExtraStress (Just ExtraStress{defaultFactors :: ExtraStress -> Maybe Ts
A.defaultFactors= Maybe Ts
mDefFactor
,prepaymentFactors :: ExtraStress -> Maybe Ts
A.prepaymentFactors = Maybe Ts
mPrepayFactor}) [Date]
ds [Rate]
ppy [Rate]
def =
case (Maybe Ts
mPrepayFactor,Maybe Ts
mDefFactor) of
(Maybe Ts
Nothing,Maybe Ts
Nothing) -> ([Rate]
ppy,[Rate]
def)
(Maybe Ts
Nothing,Just Ts
defFactor) -> ([Rate]
ppy ,Ts -> [Rate]
getTsVals (Ts -> [Rate]) -> Ts -> [Rate]
forall a b. (a -> b) -> a -> b
$ CutoffType -> Ts -> Ts -> Ts
multiplyTs CutoffType
Exc ([Date] -> [Rate] -> Ts
zipTs [Date]
ds [Rate]
def) Ts
defFactor)
(Just Ts
ppyFactor,Maybe Ts
Nothing) -> (Ts -> [Rate]
getTsVals (Ts -> [Rate]) -> Ts -> [Rate]
forall a b. (a -> b) -> a -> b
$ CutoffType -> Ts -> Ts -> Ts
multiplyTs CutoffType
Exc ([Date] -> [Rate] -> Ts
zipTs [Date]
ds [Rate]
ppy) Ts
ppyFactor, [Rate]
def)
(Just Ts
ppyFactor,Just Ts
defFactor) -> (Ts -> [Rate]
getTsVals (Ts -> [Rate]) -> Ts -> [Rate]
forall a b. (a -> b) -> a -> b
$ CutoffType -> Ts -> Ts -> Ts
multiplyTs CutoffType
Exc ([Date] -> [Rate] -> Ts
zipTs [Date]
ds [Rate]
ppy) Ts
ppyFactor
,Ts -> [Rate]
getTsVals (Ts -> [Rate]) -> Ts -> [Rate]
forall a b. (a -> b) -> a -> b
$ CutoffType -> Ts -> Ts -> Ts
multiplyTs CutoffType
Exc ([Date] -> [Rate] -> Ts
zipTs [Date]
ds [Rate]
def) Ts
defFactor)
cpr2smm :: Rate -> Rate
cpr2smm :: Rate -> Rate
cpr2smm Rate
r = Double -> Rate
forall a. Real a => a -> Rate
toRational (Double -> Rate) -> Double -> Rate
forall a b. (a -> b) -> a -> b
$ Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Rate -> Double
forall a. Fractional a => Rate -> a
fromRational Rate
r :: Double) Double -> Double -> Double
forall a. Floating a => a -> a -> a
** (Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
12)
normalPerfVector :: [Rate] -> [Rate]
normalPerfVector :: [Rate] -> [Rate]
normalPerfVector = Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
floorWith Rate
0.0 ([Rate] -> [Rate]) -> ([Rate] -> [Rate]) -> [Rate] -> [Rate]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0
buildPrepayRates :: Asset b => b -> [Date] -> Maybe A.AssetPrepayAssumption -> Either String [Rate]
buildPrepayRates :: forall b.
Asset b =>
b -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
buildPrepayRates b
_ [Date]
ds Maybe AssetPrepayAssumption
Nothing = [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> Rate -> [Rate]
forall a. Int -> a -> [a]
replicate (Int -> Int
forall a. Enum a => a -> a
pred ([Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds)) Rate
0.0
buildPrepayRates b
a [Date]
ds Maybe AssetPrepayAssumption
mPa =
[Rate] -> [Rate]
normalPerfVector ([Rate] -> [Rate]) -> Either String [Rate] -> Either String [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
case Maybe AssetPrepayAssumption
mPa of
Just (A.PrepaymentConstant Rate
r) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> Rate -> [Rate]
forall a. Int -> a -> [a]
replicate Int
size Rate
r
Just (A.PrepaymentCPR Rate
r) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Rate -> Int -> Rate
Util.toPeriodRateByInterval Rate
r (Int -> Rate) -> [Int] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Date] -> [Int]
getIntervalDays [Date]
ds
Just (A.PrepaymentVec [Rate]
vs) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ (Rate -> Int -> Rate) -> [Rate] -> [Int] -> [Rate]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
Rate -> Int -> Rate
Util.toPeriodRateByInterval
(Rate -> [Rate] -> Int -> [Rate]
forall a. a -> [a] -> Int -> [a]
paddingDefault Rate
0.0 [Rate]
vs (Int -> Int
forall a. Enum a => a -> a
pred Int
size))
([Date] -> [Int]
getIntervalDays [Date]
ds)
Just (A.PrepaymentVecPadding [Rate]
vs) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ (Rate -> Int -> Rate) -> [Rate] -> [Int] -> [Rate]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
Rate -> Int -> Rate
Util.toPeriodRateByInterval
(Rate -> [Rate] -> Int -> [Rate]
forall a. a -> [a] -> Int -> [a]
paddingDefault ([Rate] -> Rate
forall a. HasCallStack => [a] -> a
last [Rate]
vs) [Rate]
vs (Int -> Int
forall a. Enum a => a -> a
pred Int
size))
([Date] -> [Int]
getIntervalDays [Date]
ds)
Just (A.PrepayStressByTs Ts
ts AssetPrepayAssumption
x) ->
do
[Rate]
rs <- b -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
forall b.
Asset b =>
b -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
buildPrepayRates b
a [Date]
ds (AssetPrepayAssumption -> Maybe AssetPrepayAssumption
forall a. a -> Maybe a
Just AssetPrepayAssumption
x)
[Rate] -> Either String [Rate]
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Ts -> [Rate]
getTsVals (Ts -> [Rate]) -> Ts -> [Rate]
forall a b. (a -> b) -> a -> b
$ CutoffType -> Ts -> Ts -> Ts
multiplyTs CutoffType
Exc ([Date] -> [Rate] -> Ts
zipTs ([Date] -> [Date]
forall a. HasCallStack => [a] -> [a]
tail [Date]
ds) [Rate]
rs) Ts
ts
Just (A.PrepaymentPSA Rate
r) ->
let
agedTerm :: Int
agedTerm = b -> Int
forall a. Asset a => a -> Int
getPastTerms b
a
remainingTerm :: Int
remainingTerm = b -> Int
forall a. Asset a => a -> Int
getRemainTerms b
a
ppyVectorInCPR :: [Rate]
ppyVectorInCPR = (Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
r) (Rate -> Rate) -> [Rate] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate
0.002,Rate
0.004..Rate
0.06] [Rate] -> [Rate] -> [Rate]
forall a. [a] -> [a] -> [a]
++ Rate -> [Rate]
forall a. a -> [a]
repeat Rate
0.06
vectorUsed :: [Rate]
vectorUsed = Int -> [Rate] -> [Rate]
forall a. Int -> [a] -> [a]
take Int
remainingTerm ([Rate] -> [Rate]) -> [Rate] -> [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> [Rate] -> [Rate]
forall a. Int -> [a] -> [a]
drop Int
agedTerm [Rate]
ppyVectorInCPR
in
case OriginalInfo -> Period
period (b -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo b
a) of
Period
Monthly -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Rate -> Rate
cpr2smm (Rate -> Rate) -> [Rate] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
vectorUsed
Period
_ -> String -> Either String [Rate]
forall a b. a -> Either a b
Left (String -> Either String [Rate]) -> String -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ String
"PSA is only supported for monthly payment but got "String -> String -> String
forall a. [a] -> [a] -> [a]
++ Period -> String
forall a. Show a => a -> String
show (OriginalInfo -> Period
period (b -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo b
a))
Just (A.PrepaymentByTerm [[Rate]]
rs) ->
let
agedTerm :: Int
agedTerm = b -> Int
forall a. Asset a => a -> Int
getPastTerms b
a
oTerm :: Int
oTerm = OriginalInfo -> Int
originTerm (b -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo b
a)
in
case ([Rate] -> Bool) -> [[Rate]] -> Maybe [Rate]
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\[Rate]
x -> Int
oTerm Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [Rate] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rate]
x) [[Rate]]
rs of
Just [Rate]
v -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> [Rate] -> [Rate]
forall a. Int -> [a] -> [a]
drop Int
agedTerm [Rate]
v
Maybe [Rate]
Nothing -> String -> Either String [Rate]
forall a b. a -> Either a b
Left String
"Prepayment by term doesn't match the origin term"
Maybe AssetPrepayAssumption
_ -> String -> Either String [Rate]
forall a b. a -> Either a b
Left (String
"failed to find prepayment type"String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe AssetPrepayAssumption -> String
forall a. Show a => a -> String
show Maybe AssetPrepayAssumption
mPa)
where
size :: Int
size = [Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds
buildDefaultRates :: Asset b => b -> [Date] -> Maybe A.AssetDefaultAssumption -> Either String [Rate]
buildDefaultRates :: forall b.
Asset b =>
b -> [Date] -> Maybe AssetDefaultAssumption -> Either String [Rate]
buildDefaultRates b
_ [Date]
ds Maybe AssetDefaultAssumption
Nothing = [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> Rate -> [Rate]
forall a. Int -> a -> [a]
replicate (Int -> Int
forall a. Enum a => a -> a
pred ([Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds)) Rate
0.0
buildDefaultRates b
a [] Maybe AssetDefaultAssumption
mDa = String -> Either String [Rate]
forall a b. a -> Either a b
Left String
"buildDefaultRates: empty date list"
buildDefaultRates b
a [Date]
ds Maybe AssetDefaultAssumption
mDa =
[Rate] -> [Rate]
normalPerfVector ([Rate] -> [Rate]) -> Either String [Rate] -> Either String [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
case Maybe AssetDefaultAssumption
mDa of
Just (A.DefaultConstant Rate
r) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> Rate -> [Rate]
forall a. Int -> a -> [a]
replicate Int
size Rate
r
Just (A.DefaultCDR Rate
r) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Rate -> Int -> Rate
Util.toPeriodRateByInterval Rate
r (Int -> Rate) -> [Int] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Date] -> [Int]
getIntervalDays [Date]
ds
Just (A.DefaultVec [Rate]
vs) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ (Rate -> Int -> Rate) -> [Rate] -> [Int] -> [Rate]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
Rate -> Int -> Rate
Util.toPeriodRateByInterval
(Rate -> [Rate] -> Int -> [Rate]
forall a. a -> [a] -> Int -> [a]
paddingDefault Rate
0.0 [Rate]
vs (Int -> Int
forall a. Enum a => a -> a
pred Int
size))
([Date] -> [Int]
getIntervalDays [Date]
ds)
Just (A.DefaultVecPadding [Rate]
vs) -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ (Rate -> Int -> Rate) -> [Rate] -> [Int] -> [Rate]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
Rate -> Int -> Rate
Util.toPeriodRateByInterval
(Rate -> [Rate] -> Int -> [Rate]
forall a. a -> [a] -> Int -> [a]
paddingDefault ([Rate] -> Rate
forall a. HasCallStack => [a] -> a
last [Rate]
vs) [Rate]
vs (Int -> Int
forall a. Enum a => a -> a
pred Int
size))
([Date] -> [Int]
getIntervalDays [Date]
ds)
Just (A.DefaultAtEndByRate Rate
r Rate
rAtEnd)
-> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ case Int
size of
Int
0 -> []
Int
1 -> []
Int
_ -> (Rate -> Int -> Rate
Util.toPeriodRateByInterval Rate
r (Int -> Rate) -> [Int] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Date] -> [Int]
getIntervalDays ([Date] -> [Date]
forall a. HasCallStack => [a] -> [a]
init [Date]
ds)) [Rate] -> [Rate] -> [Rate]
forall a. [a] -> [a] -> [a]
++ (Rate -> Int -> Rate
Util.toPeriodRateByInterval Rate
rAtEnd (Int -> Rate) -> [Int] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Date] -> [Int]
getIntervalDays [[Date] -> Date
forall a. HasCallStack => [a] -> a
head [Date]
ds,[Date] -> Date
forall a. HasCallStack => [a] -> a
last [Date]
ds])
Just (A.DefaultStressByTs Ts
ts AssetDefaultAssumption
x) ->
do
[Rate]
rs <- b -> [Date] -> Maybe AssetDefaultAssumption -> Either String [Rate]
forall b.
Asset b =>
b -> [Date] -> Maybe AssetDefaultAssumption -> Either String [Rate]
buildDefaultRates b
a [Date]
ds (AssetDefaultAssumption -> Maybe AssetDefaultAssumption
forall a. a -> Maybe a
Just AssetDefaultAssumption
x)
let r :: [Rate]
r = Ts -> [Rate]
getTsVals (Ts -> [Rate]) -> Ts -> [Rate]
forall a b. (a -> b) -> a -> b
$ CutoffType -> Ts -> Ts -> Ts
multiplyTs CutoffType
Inc ([Date] -> [Rate] -> Ts
zipTs ([Date] -> [Date]
forall a. HasCallStack => [a] -> [a]
tail [Date]
ds) [Rate]
rs) Ts
ts
[Rate] -> Either String [Rate]
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return [Rate]
r
Just (A.DefaultByTerm [[Rate]]
rs) ->
let
agedTerm :: Int
agedTerm = b -> Int
forall a. Asset a => a -> Int
getPastTerms b
a
oTerm :: Int
oTerm = OriginalInfo -> Int
originTerm (b -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
getOriginInfo b
a)
in
case ([Rate] -> Bool) -> [[Rate]] -> Maybe [Rate]
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\[Rate]
x -> Int
oTerm Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [Rate] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rate]
x) [[Rate]]
rs of
Just [Rate]
v -> [Rate] -> Either String [Rate]
forall a b. b -> Either a b
Right ([Rate] -> Either String [Rate]) -> [Rate] -> Either String [Rate]
forall a b. (a -> b) -> a -> b
$ Int -> [Rate] -> [Rate]
forall a. Int -> [a] -> [a]
drop Int
agedTerm [Rate]
v
Maybe [Rate]
Nothing -> String -> Either String [Rate]
forall a b. a -> Either a b
Left String
"Default by term doesn't match the origin term"
Maybe AssetDefaultAssumption
_ -> String -> Either String [Rate]
forall a b. a -> Either a b
Left (String
"failed to find default rate type"String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe AssetDefaultAssumption -> String
forall a. Show a => a -> String
show Maybe AssetDefaultAssumption
mDa)
where
size :: Int
size = [Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds
getRecoveryLagAndRate :: Maybe A.RecoveryAssumption -> (Rate,Int)
getRecoveryLagAndRate :: Maybe RecoveryAssumption -> (Rate, Int)
getRecoveryLagAndRate Maybe RecoveryAssumption
Nothing = (Rate
0,Int
0)
getRecoveryLagAndRate (Just (A.Recovery (Rate
r,Int
lag))) = (Rate
r,Int
lag)
buildAssumptionPpyDefRecRate :: Asset a => a -> [Date] -> A.AssetPerfAssumption -> Either String ([Rate],[Rate],Rate,Int)
buildAssumptionPpyDefRecRate :: forall a.
Asset a =>
a
-> [Date]
-> AssetPerfAssumption
-> Either String ([Rate], [Rate], Rate, Int)
buildAssumptionPpyDefRecRate a
a [Date]
ds (A.LoanAssump Maybe AssetDefaultAssumption
mDa Maybe AssetPrepayAssumption
mPa Maybe RecoveryAssumption
mRa Maybe ExtraStress
mESa) = a
-> [Date]
-> AssetPerfAssumption
-> Either String ([Rate], [Rate], Rate, Int)
forall a.
Asset a =>
a
-> [Date]
-> AssetPerfAssumption
-> Either String ([Rate], [Rate], Rate, Int)
buildAssumptionPpyDefRecRate a
a [Date]
ds (Maybe AssetDefaultAssumption
-> Maybe AssetPrepayAssumption
-> Maybe RecoveryAssumption
-> Maybe ExtraStress
-> AssetPerfAssumption
A.MortgageAssump Maybe AssetDefaultAssumption
mDa Maybe AssetPrepayAssumption
mPa Maybe RecoveryAssumption
mRa Maybe ExtraStress
mESa)
buildAssumptionPpyDefRecRate a
a [Date]
ds (A.MortgageAssump Maybe AssetDefaultAssumption
mDa Maybe AssetPrepayAssumption
mPa Maybe RecoveryAssumption
mRa Maybe ExtraStress
mESa)
= let
size :: Int
size = [Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds
zeros :: [Double]
zeros = Int -> Double -> [Double]
forall a. Int -> a -> [a]
replicate Int
size Double
0.0
(Rate
recoveryRate,Int
recoveryLag) = Maybe RecoveryAssumption -> (Rate, Int)
getRecoveryLagAndRate Maybe RecoveryAssumption
mRa
in
do
[Rate]
prepayRates <- a -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
forall b.
Asset b =>
b -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
buildPrepayRates a
a [Date]
ds Maybe AssetPrepayAssumption
mPa
[Rate]
defaultRates <- a -> [Date] -> Maybe AssetDefaultAssumption -> Either String [Rate]
forall b.
Asset b =>
b -> [Date] -> Maybe AssetDefaultAssumption -> Either String [Rate]
buildDefaultRates a
a [Date]
ds Maybe AssetDefaultAssumption
mDa
let ([Rate]
prepayRates2,[Rate]
defaultRates2) = Maybe ExtraStress -> [Date] -> [Rate] -> [Rate] -> ([Rate], [Rate])
applyExtraStress Maybe ExtraStress
mESa [Date]
ds [Rate]
prepayRates [Rate]
defaultRates
([Rate], [Rate], Rate, Int)
-> Either String ([Rate], [Rate], Rate, Int)
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Rate]
prepayRates2,[Rate]
defaultRates2,Rate
recoveryRate,Int
recoveryLag)
getDefaultDelinqAssump :: Maybe A.AssetDelinquencyAssumption -> [Date] -> ([Rate],Int,Rate)
getDefaultDelinqAssump :: Maybe AssetDelinquencyAssumption -> [Date] -> ([Rate], Int, Rate)
getDefaultDelinqAssump Maybe AssetDelinquencyAssumption
Nothing [Date]
ds = (Int -> Rate -> [Rate]
forall a. Int -> a -> [a]
replicate ([Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds) Rate
0.0, Int
0, Rate
0.0)
getDefaultDelinqAssump (Just (A.DelinqCDR Rate
r (Int
lag,Rate
pct))) [Date]
ds = ((Int -> Rate) -> [Int] -> [Rate]
forall a b. (a -> b) -> [a] -> [b]
map (Rate -> Int -> Rate
Util.toPeriodRateByInterval Rate
r) ([Date] -> [Int]
getIntervalDays [Date]
ds)
,Int
lag
,Rate
pct)
getDefaultLagAndRate :: Maybe A.RecoveryAssumption -> (Rate,Int)
getDefaultLagAndRate :: Maybe RecoveryAssumption -> (Rate, Int)
getDefaultLagAndRate Maybe RecoveryAssumption
Nothing = (Rate
0,Int
0)
getDefaultLagAndRate (Just (A.Recovery (Rate
r,Int
lag))) = (Rate
r,Int
lag)
buildAssumptionPpyDelinqDefRecRate :: Asset a => a -> [Date] -> A.AssetPerfAssumption -> Either String ([Rate],[Rate],(Rate,Lag),Rate,Int)
buildAssumptionPpyDelinqDefRecRate :: forall a.
Asset a =>
a
-> [Date]
-> AssetPerfAssumption
-> Either String ([Rate], [Rate], (Rate, Int), Rate, Int)
buildAssumptionPpyDelinqDefRecRate a
_ [Date]
ds (A.MortgageDeqAssump Maybe AssetDelinquencyAssumption
mDeqDefault Maybe AssetPrepayAssumption
mPa Maybe RecoveryAssumption
mRa (Just ExtraStress
_)) = String -> Either String ([Rate], [Rate], (Rate, Int), Rate, Int)
forall a b. a -> Either a b
Left String
"Delinq assumption doesn't support extra stress"
buildAssumptionPpyDelinqDefRecRate a
a [Date]
ds (A.MortgageDeqAssump Maybe AssetDelinquencyAssumption
mDeqDefault Maybe AssetPrepayAssumption
mPa Maybe RecoveryAssumption
mRa Maybe ExtraStress
Nothing)
= let
(Rate
recoveryRate,Int
recoveryLag) = Maybe RecoveryAssumption -> (Rate, Int)
getRecoveryLagAndRate Maybe RecoveryAssumption
mRa
zeros :: [Rate]
zeros = Int -> Rate -> [Rate]
forall a. Int -> a -> [a]
replicate ([Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds) Rate
0.0
([Rate]
delinqRates,Int
defaultLag,Rate
defaultPct) = case Maybe AssetDelinquencyAssumption
mDeqDefault of
Maybe AssetDelinquencyAssumption
Nothing -> ([Rate]
zeros,Int
0,Rate
0.0)
Just (A.DelinqCDR Rate
r (Int
lag,Rate
pct)) ->
((Int -> Rate) -> [Int] -> [Rate]
forall a b. (a -> b) -> [a] -> [b]
map (Rate -> Int -> Rate
Util.toPeriodRateByInterval Rate
r) ([Date] -> [Int]
getIntervalDays [Date]
ds)
,Int
lag
,Rate
pct)
in
do
[Rate]
prepayRates <- a -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
forall b.
Asset b =>
b -> [Date] -> Maybe AssetPrepayAssumption -> Either String [Rate]
buildPrepayRates a
a [Date]
ds Maybe AssetPrepayAssumption
mPa
([Rate], [Rate], (Rate, Int), Rate, Int)
-> Either String ([Rate], [Rate], (Rate, Int), Rate, Int)
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Rate]
prepayRates,[Rate]
delinqRates,(Rate
defaultPct,Int
defaultLag),Rate
recoveryRate, Int
recoveryLag)
calcRecoveriesFromDefault :: Balance -> Rate -> [Rate] -> [Amount]
calcRecoveriesFromDefault :: Balance -> Rate -> [Rate] -> [Balance]
calcRecoveriesFromDefault Balance
bal Rate
recoveryRate [Rate]
recoveryTiming
= Balance -> Rate -> Balance
mulBR Balance
recoveryAmt (Rate -> Balance) -> [Rate] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
recoveryTiming
where
recoveryAmt :: Balance
recoveryAmt = Balance -> Rate -> Balance
mulBR Balance
bal Rate
recoveryRate
priceAsset :: Asset a => a -> Date -> PricingMethod -> A.AssetPerf -> Maybe [RateAssumption] -> CutoffType
-> Either String PriceResult
priceAsset :: forall a.
Asset a =>
a
-> Date
-> PricingMethod
-> AssetPerf
-> Maybe [RateAssumption]
-> CutoffType
-> Either String PriceResult
priceAsset a
m Date
d (PVCurve Ts
curve) AssetPerf
assumps Maybe [RateAssumption]
mRates CutoffType
cType
= let
cr :: Duration
cr = a -> Duration
forall a. Asset a => a -> Duration
getCurrentRate a
m
pDays :: [Date]
pDays = a -> Date
forall a. Asset a => a -> Date
Asset.getOriginDate a
mDate -> [Date] -> [Date]
forall a. a -> [a] -> [a]
:(a -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
getPaymentDates a
m Int
0)
cb :: Balance
cb = a -> Balance
forall a. Asset a => a -> Balance
getCurrentBal a
m
in
case a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Balance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Balance)
projCashflow a
m Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates of
Right (CF.CashFlowFrame BeginStatus
_ [TsRow]
txns,Map CutoffFields Balance
_) ->
let
ds :: [Date]
ds = TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate (TsRow -> Date) -> [TsRow] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
txns
accruedInt :: Balance
accruedInt = case [Date]
ds of
[] -> Balance
0
(Date
fstTxnDate:[Date]
_) ->
let
accStartDate :: Date
accStartDate = [Date] -> Date
forall a. HasCallStack => [a] -> a
last ([Date] -> Date) -> [Date] -> Date
forall a b. (a -> b) -> a -> b
$ (Date -> Bool) -> [Date] -> [Date]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
< Date
fstTxnDate) [Date]
pDays
in
Balance -> Rate -> Balance
mulBR (Balance -> Duration -> Balance
mulBIR Balance
cb Duration
cr) (DayCount -> Date -> Date -> Rate
yearCountFraction DayCount
DC_ACT_365F Date
accStartDate Date
d)
amts :: [Balance]
amts = TsRow -> Balance
CF.tsTotalCash (TsRow -> Balance) -> [TsRow] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (case CutoffType
cType of
CutoffType
Exc -> Balance -> [TsRow] -> [TsRow]
CF.clawbackInt Balance
accruedInt [TsRow]
txns
CutoffType
Inc -> [TsRow]
txns)
pv :: Balance
pv = Ts -> Date -> [Date] -> [Balance] -> Balance
pv3 Ts
curve Date
d [Date]
ds [Balance]
amts
wal :: Balance
wal = TimeHorizion -> Balance -> Date -> [(Balance, Date)] -> Balance
calcWAL TimeHorizion
ByYear Balance
cb Date
d ([Balance] -> [Date] -> [(Balance, Date)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Balance]
amts [Date]
ds)
duration :: Duration
duration = Rate -> Duration
forall a. Fractional a => Rate -> a
fromRational (Rate -> Duration) -> Rate -> Duration
forall a b. (a -> b) -> a -> b
$ DayCount -> Date -> [(Date, Balance)] -> Ts -> Rate
calcDuration DayCount
DC_ACT_365F Date
d ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
ds [Balance]
amts) Ts
curve
convexity :: Duration
convexity = Rate -> Duration
forall a. Fractional a => Rate -> a
fromRational (Rate -> Duration) -> Rate -> Duration
forall a b. (a -> b) -> a -> b
$ DayCount -> Date -> [(Date, Balance)] -> Ts -> Rate
calcConvexity DayCount
DC_ACT_365F Date
d ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
ds [Balance]
amts) Ts
curve
in
PriceResult -> Either String PriceResult
forall a b. b -> Either a b
Right (PriceResult -> Either String PriceResult)
-> PriceResult -> Either String PriceResult
forall a b. (a -> b) -> a -> b
$ Balance
-> Balance -> Duration -> Duration -> Balance -> PriceResult
AssetPrice Balance
pv Balance
wal Duration
duration Duration
convexity Balance
accruedInt
Left String
x -> String -> Either String PriceResult
forall a b. a -> Either a b
Left String
x
priceAsset a
m Date
d (BalanceFactor Rate
currentFactor Rate
defaultedFactor) AssetPerf
assumps Maybe [RateAssumption]
mRates CutoffType
cType
= let
cb :: Balance
cb = a -> Balance
forall a. Asset a => a -> Balance
getCurrentBal a
m
val :: Balance
val = if a -> Bool
forall a. Asset a => a -> Bool
isDefaulted a
m then
Balance -> Rate -> Balance
mulBR Balance
cb Rate
defaultedFactor
else
Balance -> Rate -> Balance
mulBR Balance
cb Rate
currentFactor
in
case a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Balance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Balance)
projCashflow a
m Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates of
Right (CF.CashFlowFrame BeginStatus
_ [TsRow]
txns,Map CutoffFields Balance
_) ->
let ds :: [Date]
ds = TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate (TsRow -> Date) -> [TsRow] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
txns
amts :: [Balance]
amts = TsRow -> Balance
CF.tsTotalCash (TsRow -> Balance) -> [TsRow] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
txns
wal :: Balance
wal = TimeHorizion -> Balance -> Date -> [(Balance, Date)] -> Balance
calcWAL TimeHorizion
ByYear Balance
cb Date
d ([Balance] -> [Date] -> [(Balance, Date)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Balance]
amts [Date]
ds)
in
PriceResult -> Either String PriceResult
forall a b. b -> Either a b
Right (PriceResult -> Either String PriceResult)
-> PriceResult -> Either String PriceResult
forall a b. (a -> b) -> a -> b
$ Balance
-> Balance -> Duration -> Duration -> Balance -> PriceResult
AssetPrice Balance
val Balance
wal (-Duration
1) (-Duration
1) (-Balance
1)
Left String
x -> String -> Either String PriceResult
forall a b. a -> Either a b
Left String
x
priceAsset a
m Date
d (PvRate Duration
r) AssetPerf
assumps Maybe [RateAssumption]
mRates CutoffType
cType
= let
cb :: Balance
cb = a -> Balance
forall a. Asset a => a -> Balance
getCurrentBal a
m
pDays :: [Date]
pDays = a -> Date
forall a. Asset a => a -> Date
Asset.getOriginDate a
mDate -> [Date] -> [Date]
forall a. a -> [a] -> [a]
:a -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
getPaymentDates a
m Int
0
cr :: Duration
cr = a -> Duration
forall a. Asset a => a -> Duration
getCurrentRate a
m
in
case a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Balance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either String (CashFlowFrame, Map CutoffFields Balance)
projCashflow a
m Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates of
Right (CF.CashFlowFrame BeginStatus
_ [TsRow]
txns,Map CutoffFields Balance
_) ->
let ds :: [Date]
ds = TsRow -> Date
forall ts. TimeSeries ts => ts -> Date
getDate (TsRow -> Date) -> [TsRow] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TsRow]
txns
accruedInt :: Balance
accruedInt = case [Date]
ds of
[] -> Balance
0
(Date
fstTxnDate:[Date]
_) ->
let
accStartDate :: Date
accStartDate = [Date] -> Date
forall a. HasCallStack => [a] -> a
last ([Date] -> Date) -> [Date] -> Date
forall a b. (a -> b) -> a -> b
$ (Date -> Bool) -> [Date] -> [Date]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Date -> Date -> Bool
forall a. Ord a => a -> a -> Bool
< Date
fstTxnDate) [Date]
pDays
in
Balance -> Rate -> Balance
mulBR (Balance -> Duration -> Balance
mulBIR Balance
cb Duration
cr) (DayCount -> Date -> Date -> Rate
yearCountFraction DayCount
DC_ACT_365F Date
accStartDate Date
d)
amts :: [Balance]
amts = TsRow -> Balance
CF.tsTotalCash (TsRow -> Balance) -> [TsRow] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (case CutoffType
cType of
CutoffType
Exc -> Balance -> [TsRow] -> [TsRow]
CF.clawbackInt Balance
accruedInt [TsRow]
txns
CutoffType
Inc -> [TsRow]
txns)
wal :: Balance
wal = TimeHorizion -> Balance -> Date -> [(Balance, Date)] -> Balance
calcWAL TimeHorizion
ByYear Balance
cb Date
d ([Balance] -> [Date] -> [(Balance, Date)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Balance]
amts [Date]
ds)
pv :: Balance
pv = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Balance] -> Balance) -> [Balance] -> Balance
forall a b. (a -> b) -> a -> b
$ (Date -> Balance -> Balance) -> [Date] -> [Balance] -> [Balance]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Duration -> Date -> Date -> Balance -> Balance
pv2 Duration
r Date
d) [Date]
ds [Balance]
amts
curve :: Ts
curve = [(Date, Rate)] -> Ts
mkTs ([(Date, Rate)] -> Ts) -> [(Date, Rate)] -> Ts
forall a b. (a -> b) -> a -> b
$ [Date] -> [Rate] -> [(Date, Rate)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
ds (Rate -> [Rate]
forall a. a -> [a]
repeat (Duration -> Rate
forall a. Real a => a -> Rate
toRational Duration
r))
duration :: Duration
duration = Rate -> Duration
forall a. Fractional a => Rate -> a
fromRational (Rate -> Duration) -> Rate -> Duration
forall a b. (a -> b) -> a -> b
$ DayCount -> Date -> [(Date, Balance)] -> Ts -> Rate
calcDuration DayCount
DC_ACT_365F Date
d ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
ds [Balance]
amts) Ts
curve
convexity :: Duration
convexity = Rate -> Duration
forall a. Fractional a => Rate -> a
fromRational (Rate -> Duration) -> Rate -> Duration
forall a b. (a -> b) -> a -> b
$ DayCount -> Date -> [(Date, Balance)] -> Ts -> Rate
calcConvexity DayCount
DC_ACT_365F Date
d ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
ds [Balance]
amts) Ts
curve
in
PriceResult -> Either String PriceResult
forall a b. b -> Either a b
Right (PriceResult -> Either String PriceResult)
-> PriceResult -> Either String PriceResult
forall a b. (a -> b) -> a -> b
$ Balance
-> Balance -> Duration -> Duration -> Balance -> PriceResult
AssetPrice Balance
pv Balance
wal Duration
duration Duration
convexity Balance
accruedInt
Left String
x -> String -> Either String PriceResult
forall a b. a -> Either a b
Left String
x