{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}
module Assumptions (BondPricingInput(..),IrrType(..)
,AssumptionInput(..),ApplyAssumptionType(..)
,lookupAssumptionByIdx,lookupRate,AssetPerfAssumption(..)
,ExtraStress(..),RevolvingAssumption(..)
,AssetPrepayAssumption(..),AssetDefaultAssumption(..),RecoveryAssumption(..)
,getRateAssumption,projRates,lookupRate0
,LeaseAssetGapAssump(..)
,LeaseAssetRentAssump(..)
,NonPerfAssumption(..),AssetPerf
,AssetDelinquencyAssumption(..)
,AssetDelinqPerfAssumption(..),AssetDefaultedPerfAssumption(..)
,IssueBondEvent(..)
,TagMatchRule(..),ObligorStrategy(..),RefiEvent(..),InspectType(..)
,FieldMatchRule(..),CallOpt(..)
,_MortgageAssump,_MortgageDeqAssump,_LeaseAssump,_LoanAssump,_InstallmentAssump
,_ReceivableAssump,_FixedAssetAssump
,stressDefaultAssump,applyAssumptionTypeAssetPerf,TradeType(..)
,LeaseEndType(..),LeaseDefaultType(..),stressPrepaymentAssump,StopBy(..)
)
where
import Call as C
import Lib (Ts(..),TsPoint(..),toDate,mkRateTs)
import Liability (Bond,InterestInfo)
import Util
import DateUtil
import qualified Data.Map as Map
import Data.List
import qualified Data.Set as Set
import Data.Aeson hiding (json)
import Language.Haskell.TH
import Data.Aeson.TH
import Data.Aeson.Types
import Types
import qualified Data.Time as T
import Data.Fixed
import Data.Ratio
import Revolving
import GHC.Generics
import AssetClass.AssetBase
import Debug.Trace
import InterestRate
import Control.Lens hiding (Index)
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 AssetPerf = (AssetPerfAssumption,AssetDelinqPerfAssumption,AssetDefaultedPerfAssumption)
type StratPerfByIdx = ([Int],AssetPerf)
lookupAssumptionByIdx :: [StratPerfByIdx] -> Int -> Either String AssetPerf
lookupAssumptionByIdx :: [StratPerfByIdx]
-> Int
-> Either
String
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
lookupAssumptionByIdx [StratPerfByIdx]
sbi Int
i
= case (StratPerfByIdx -> Bool)
-> [StratPerfByIdx] -> Maybe StratPerfByIdx
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\([Int]
indxs,(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
_) -> Int -> Set Int -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Int
i ([Int] -> Set Int
forall a. Ord a => [a] -> Set a
Set.fromList [Int]
indxs) ) [StratPerfByIdx]
sbi of
Just ([Int]
_, (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
aps ) -> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> Either
String
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
forall a b. b -> Either a b
Right (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
aps
Maybe StratPerfByIdx
Nothing -> String
-> Either
String
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
forall a b. a -> Either a b
Left (String
"Lookup assumption by ID: Can't find idx"String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"in starfication list"String -> String -> String
forall a. [a] -> [a] -> [a]
++ [StratPerfByIdx] -> String
forall a. Show a => a -> String
show [StratPerfByIdx]
sbi)
type ObligorTagStr = String
data TagMatchRule = TagEq
| TagSubset
| TagSuperset
| TagAny
| TagNot TagMatchRule
deriving (Int -> TagMatchRule -> String -> String
[TagMatchRule] -> String -> String
TagMatchRule -> String
(Int -> TagMatchRule -> String -> String)
-> (TagMatchRule -> String)
-> ([TagMatchRule] -> String -> String)
-> Show TagMatchRule
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TagMatchRule -> String -> String
showsPrec :: Int -> TagMatchRule -> String -> String
$cshow :: TagMatchRule -> String
show :: TagMatchRule -> String
$cshowList :: [TagMatchRule] -> String -> String
showList :: [TagMatchRule] -> String -> String
Show, (forall x. TagMatchRule -> Rep TagMatchRule x)
-> (forall x. Rep TagMatchRule x -> TagMatchRule)
-> Generic TagMatchRule
forall x. Rep TagMatchRule x -> TagMatchRule
forall x. TagMatchRule -> Rep TagMatchRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TagMatchRule -> Rep TagMatchRule x
from :: forall x. TagMatchRule -> Rep TagMatchRule x
$cto :: forall x. Rep TagMatchRule x -> TagMatchRule
to :: forall x. Rep TagMatchRule x -> TagMatchRule
Generic, ReadPrec [TagMatchRule]
ReadPrec TagMatchRule
Int -> ReadS TagMatchRule
ReadS [TagMatchRule]
(Int -> ReadS TagMatchRule)
-> ReadS [TagMatchRule]
-> ReadPrec TagMatchRule
-> ReadPrec [TagMatchRule]
-> Read TagMatchRule
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TagMatchRule
readsPrec :: Int -> ReadS TagMatchRule
$creadList :: ReadS [TagMatchRule]
readList :: ReadS [TagMatchRule]
$creadPrec :: ReadPrec TagMatchRule
readPrec :: ReadPrec TagMatchRule
$creadListPrec :: ReadPrec [TagMatchRule]
readListPrec :: ReadPrec [TagMatchRule]
Read)
data FieldMatchRule = FieldIn String [String]
| FieldCmp String Cmp Double
| FieldInRange String RangeType Double Double
| FieldNot FieldMatchRule
deriving (Int -> FieldMatchRule -> String -> String
[FieldMatchRule] -> String -> String
FieldMatchRule -> String
(Int -> FieldMatchRule -> String -> String)
-> (FieldMatchRule -> String)
-> ([FieldMatchRule] -> String -> String)
-> Show FieldMatchRule
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FieldMatchRule -> String -> String
showsPrec :: Int -> FieldMatchRule -> String -> String
$cshow :: FieldMatchRule -> String
show :: FieldMatchRule -> String
$cshowList :: [FieldMatchRule] -> String -> String
showList :: [FieldMatchRule] -> String -> String
Show, (forall x. FieldMatchRule -> Rep FieldMatchRule x)
-> (forall x. Rep FieldMatchRule x -> FieldMatchRule)
-> Generic FieldMatchRule
forall x. Rep FieldMatchRule x -> FieldMatchRule
forall x. FieldMatchRule -> Rep FieldMatchRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FieldMatchRule -> Rep FieldMatchRule x
from :: forall x. FieldMatchRule -> Rep FieldMatchRule x
$cto :: forall x. Rep FieldMatchRule x -> FieldMatchRule
to :: forall x. Rep FieldMatchRule x -> FieldMatchRule
Generic, ReadPrec [FieldMatchRule]
ReadPrec FieldMatchRule
Int -> ReadS FieldMatchRule
ReadS [FieldMatchRule]
(Int -> ReadS FieldMatchRule)
-> ReadS [FieldMatchRule]
-> ReadPrec FieldMatchRule
-> ReadPrec [FieldMatchRule]
-> Read FieldMatchRule
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldMatchRule
readsPrec :: Int -> ReadS FieldMatchRule
$creadList :: ReadS [FieldMatchRule]
readList :: ReadS [FieldMatchRule]
$creadPrec :: ReadPrec FieldMatchRule
readPrec :: ReadPrec FieldMatchRule
$creadListPrec :: ReadPrec [FieldMatchRule]
readListPrec :: ReadPrec [FieldMatchRule]
Read)
data ObligorStrategy = ObligorById [String] AssetPerf
| ObligorByTag [ObligorTagStr] TagMatchRule AssetPerf
| ObligorByField [FieldMatchRule] AssetPerf
| ObligorByDefault AssetPerf
deriving (Int -> ObligorStrategy -> String -> String
[ObligorStrategy] -> String -> String
ObligorStrategy -> String
(Int -> ObligorStrategy -> String -> String)
-> (ObligorStrategy -> String)
-> ([ObligorStrategy] -> String -> String)
-> Show ObligorStrategy
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObligorStrategy -> String -> String
showsPrec :: Int -> ObligorStrategy -> String -> String
$cshow :: ObligorStrategy -> String
show :: ObligorStrategy -> String
$cshowList :: [ObligorStrategy] -> String -> String
showList :: [ObligorStrategy] -> String -> String
Show, (forall x. ObligorStrategy -> Rep ObligorStrategy x)
-> (forall x. Rep ObligorStrategy x -> ObligorStrategy)
-> Generic ObligorStrategy
forall x. Rep ObligorStrategy x -> ObligorStrategy
forall x. ObligorStrategy -> Rep ObligorStrategy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ObligorStrategy -> Rep ObligorStrategy x
from :: forall x. ObligorStrategy -> Rep ObligorStrategy x
$cto :: forall x. Rep ObligorStrategy x -> ObligorStrategy
to :: forall x. Rep ObligorStrategy x -> ObligorStrategy
Generic, ReadPrec [ObligorStrategy]
ReadPrec ObligorStrategy
Int -> ReadS ObligorStrategy
ReadS [ObligorStrategy]
(Int -> ReadS ObligorStrategy)
-> ReadS [ObligorStrategy]
-> ReadPrec ObligorStrategy
-> ReadPrec [ObligorStrategy]
-> Read ObligorStrategy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObligorStrategy
readsPrec :: Int -> ReadS ObligorStrategy
$creadList :: ReadS [ObligorStrategy]
readList :: ReadS [ObligorStrategy]
$creadPrec :: ReadPrec ObligorStrategy
readPrec :: ReadPrec ObligorStrategy
$creadListPrec :: ReadPrec [ObligorStrategy]
readListPrec :: ReadPrec [ObligorStrategy]
Read)
data ApplyAssumptionType = PoolLevel AssetPerf
| ByIndex [StratPerfByIdx]
| ByName (Map.Map PoolId AssetPerf)
| ByPoolId (Map.Map PoolId ApplyAssumptionType)
| ByObligor [ObligorStrategy]
| ByDealName (Map.Map DealName (ApplyAssumptionType, NonPerfAssumption))
deriving (Int -> ApplyAssumptionType -> String -> String
[ApplyAssumptionType] -> String -> String
ApplyAssumptionType -> String
(Int -> ApplyAssumptionType -> String -> String)
-> (ApplyAssumptionType -> String)
-> ([ApplyAssumptionType] -> String -> String)
-> Show ApplyAssumptionType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ApplyAssumptionType -> String -> String
showsPrec :: Int -> ApplyAssumptionType -> String -> String
$cshow :: ApplyAssumptionType -> String
show :: ApplyAssumptionType -> String
$cshowList :: [ApplyAssumptionType] -> String -> String
showList :: [ApplyAssumptionType] -> String -> String
Show, (forall x. ApplyAssumptionType -> Rep ApplyAssumptionType x)
-> (forall x. Rep ApplyAssumptionType x -> ApplyAssumptionType)
-> Generic ApplyAssumptionType
forall x. Rep ApplyAssumptionType x -> ApplyAssumptionType
forall x. ApplyAssumptionType -> Rep ApplyAssumptionType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ApplyAssumptionType -> Rep ApplyAssumptionType x
from :: forall x. ApplyAssumptionType -> Rep ApplyAssumptionType x
$cto :: forall x. Rep ApplyAssumptionType x -> ApplyAssumptionType
to :: forall x. Rep ApplyAssumptionType x -> ApplyAssumptionType
Generic)
applyAssumptionTypeAssetPerf :: Traversal' ApplyAssumptionType AssetPerf
applyAssumptionTypeAssetPerf :: Traversal'
ApplyAssumptionType
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
applyAssumptionTypeAssetPerf (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f = ApplyAssumptionType -> f ApplyAssumptionType
go
where
go :: ApplyAssumptionType -> f ApplyAssumptionType
go (PoolLevel (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
x) = (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ApplyAssumptionType
PoolLevel ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ApplyAssumptionType)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f ApplyAssumptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
x
go (ByIndex [StratPerfByIdx]
strats) = [StratPerfByIdx] -> ApplyAssumptionType
ByIndex ([StratPerfByIdx] -> ApplyAssumptionType)
-> f [StratPerfByIdx] -> f ApplyAssumptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (StratPerfByIdx -> f StratPerfByIdx)
-> [StratPerfByIdx] -> f [StratPerfByIdx]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\([Int]
idxs,(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
aps) -> ([Int]
idxs,) ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> StratPerfByIdx)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f StratPerfByIdx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
aps) [StratPerfByIdx]
strats
go (ByName Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
m) = Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ApplyAssumptionType
ByName (Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ApplyAssumptionType)
-> f (Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption))
-> f ApplyAssumptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption))
-> Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map PoolId a -> f (Map PoolId b)
traverse (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f Map
PoolId
(AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
m
go (ByObligor [ObligorStrategy]
os) = [ObligorStrategy] -> ApplyAssumptionType
ByObligor ([ObligorStrategy] -> ApplyAssumptionType)
-> f [ObligorStrategy] -> f ApplyAssumptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ObligorStrategy -> f ObligorStrategy)
-> [ObligorStrategy] -> f [ObligorStrategy]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\case
ObligorById [String]
ids (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap -> [String]
-> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy
ObligorById [String]
ids ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f ObligorStrategy
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap
ObligorByTag [String]
tags TagMatchRule
m (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap -> [String]
-> TagMatchRule
-> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy
ObligorByTag [String]
tags TagMatchRule
m ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f ObligorStrategy
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap
ObligorByField [FieldMatchRule]
fs (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap -> [FieldMatchRule]
-> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy
ObligorByField [FieldMatchRule]
fs ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f ObligorStrategy
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap
ObligorByDefault (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap -> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy
ObligorByDefault ((AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> ObligorStrategy)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f ObligorStrategy
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
-> f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
f (AssetPerfAssumption, AssetDelinqPerfAssumption,
AssetDefaultedPerfAssumption)
ap
) [ObligorStrategy]
os
go (ByPoolId Map PoolId ApplyAssumptionType
m) = Map PoolId ApplyAssumptionType -> ApplyAssumptionType
ByPoolId (Map PoolId ApplyAssumptionType -> ApplyAssumptionType)
-> f (Map PoolId ApplyAssumptionType) -> f ApplyAssumptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ApplyAssumptionType -> f ApplyAssumptionType)
-> Map PoolId ApplyAssumptionType
-> f (Map PoolId ApplyAssumptionType)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map PoolId a -> f (Map PoolId b)
traverse ApplyAssumptionType -> f ApplyAssumptionType
go Map PoolId ApplyAssumptionType
m
go (ByDealName Map String (ApplyAssumptionType, NonPerfAssumption)
m) = Map String (ApplyAssumptionType, NonPerfAssumption)
-> ApplyAssumptionType
ByDealName (Map String (ApplyAssumptionType, NonPerfAssumption)
-> ApplyAssumptionType)
-> f (Map String (ApplyAssumptionType, NonPerfAssumption))
-> f ApplyAssumptionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((ApplyAssumptionType, NonPerfAssumption)
-> f (ApplyAssumptionType, NonPerfAssumption))
-> Map String (ApplyAssumptionType, NonPerfAssumption)
-> f (Map String (ApplyAssumptionType, NonPerfAssumption))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map String a -> f (Map String b)
traverse (\(ApplyAssumptionType
a,NonPerfAssumption
b) -> (,) (ApplyAssumptionType
-> NonPerfAssumption -> (ApplyAssumptionType, NonPerfAssumption))
-> f ApplyAssumptionType
-> f (NonPerfAssumption
-> (ApplyAssumptionType, NonPerfAssumption))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ApplyAssumptionType -> f ApplyAssumptionType
go ApplyAssumptionType
a f (NonPerfAssumption -> (ApplyAssumptionType, NonPerfAssumption))
-> f NonPerfAssumption
-> f (ApplyAssumptionType, NonPerfAssumption)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NonPerfAssumption -> f NonPerfAssumption
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NonPerfAssumption
b) Map String (ApplyAssumptionType, NonPerfAssumption)
m
type RateFormula = DealStats
type BalanceFormula = DealStats
data IssueBondEvent = IssueBondEvent (Maybe Pre) BondName AccName Bond (Maybe BalanceFormula) (Maybe RateFormula)
| FundingBondEvent (Maybe Pre) BondName AccName Balance
deriving (Int -> IssueBondEvent -> String -> String
[IssueBondEvent] -> String -> String
IssueBondEvent -> String
(Int -> IssueBondEvent -> String -> String)
-> (IssueBondEvent -> String)
-> ([IssueBondEvent] -> String -> String)
-> Show IssueBondEvent
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> IssueBondEvent -> String -> String
showsPrec :: Int -> IssueBondEvent -> String -> String
$cshow :: IssueBondEvent -> String
show :: IssueBondEvent -> String
$cshowList :: [IssueBondEvent] -> String -> String
showList :: [IssueBondEvent] -> String -> String
Show, (forall x. IssueBondEvent -> Rep IssueBondEvent x)
-> (forall x. Rep IssueBondEvent x -> IssueBondEvent)
-> Generic IssueBondEvent
forall x. Rep IssueBondEvent x -> IssueBondEvent
forall x. IssueBondEvent -> Rep IssueBondEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IssueBondEvent -> Rep IssueBondEvent x
from :: forall x. IssueBondEvent -> Rep IssueBondEvent x
$cto :: forall x. Rep IssueBondEvent x -> IssueBondEvent
to :: forall x. Rep IssueBondEvent x -> IssueBondEvent
Generic, ReadPrec [IssueBondEvent]
ReadPrec IssueBondEvent
Int -> ReadS IssueBondEvent
ReadS [IssueBondEvent]
(Int -> ReadS IssueBondEvent)
-> ReadS [IssueBondEvent]
-> ReadPrec IssueBondEvent
-> ReadPrec [IssueBondEvent]
-> Read IssueBondEvent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IssueBondEvent
readsPrec :: Int -> ReadS IssueBondEvent
$creadList :: ReadS [IssueBondEvent]
readList :: ReadS [IssueBondEvent]
$creadPrec :: ReadPrec IssueBondEvent
readPrec :: ReadPrec IssueBondEvent
$creadListPrec :: ReadPrec [IssueBondEvent]
readListPrec :: ReadPrec [IssueBondEvent]
Read)
data RefiEvent = RefiRate AccountName BondName InterestInfo
| RefiBond AccountName Bond
| RefiEvents [RefiEvent]
deriving (Int -> RefiEvent -> String -> String
[RefiEvent] -> String -> String
RefiEvent -> String
(Int -> RefiEvent -> String -> String)
-> (RefiEvent -> String)
-> ([RefiEvent] -> String -> String)
-> Show RefiEvent
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RefiEvent -> String -> String
showsPrec :: Int -> RefiEvent -> String -> String
$cshow :: RefiEvent -> String
show :: RefiEvent -> String
$cshowList :: [RefiEvent] -> String -> String
showList :: [RefiEvent] -> String -> String
Show, (forall x. RefiEvent -> Rep RefiEvent x)
-> (forall x. Rep RefiEvent x -> RefiEvent) -> Generic RefiEvent
forall x. Rep RefiEvent x -> RefiEvent
forall x. RefiEvent -> Rep RefiEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RefiEvent -> Rep RefiEvent x
from :: forall x. RefiEvent -> Rep RefiEvent x
$cto :: forall x. Rep RefiEvent x -> RefiEvent
to :: forall x. Rep RefiEvent x -> RefiEvent
Generic, ReadPrec [RefiEvent]
ReadPrec RefiEvent
Int -> ReadS RefiEvent
ReadS [RefiEvent]
(Int -> ReadS RefiEvent)
-> ReadS [RefiEvent]
-> ReadPrec RefiEvent
-> ReadPrec [RefiEvent]
-> Read RefiEvent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RefiEvent
readsPrec :: Int -> ReadS RefiEvent
$creadList :: ReadS [RefiEvent]
readList :: ReadS [RefiEvent]
$creadPrec :: ReadPrec RefiEvent
readPrec :: ReadPrec RefiEvent
$creadListPrec :: ReadPrec [RefiEvent]
readListPrec :: ReadPrec [RefiEvent]
Read)
data InspectType = InspectPt DatePattern DealStats
| InspectRpt DatePattern [DealStats]
deriving (Int -> InspectType -> String -> String
[InspectType] -> String -> String
InspectType -> String
(Int -> InspectType -> String -> String)
-> (InspectType -> String)
-> ([InspectType] -> String -> String)
-> Show InspectType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InspectType -> String -> String
showsPrec :: Int -> InspectType -> String -> String
$cshow :: InspectType -> String
show :: InspectType -> String
$cshowList :: [InspectType] -> String -> String
showList :: [InspectType] -> String -> String
Show, (forall x. InspectType -> Rep InspectType x)
-> (forall x. Rep InspectType x -> InspectType)
-> Generic InspectType
forall x. Rep InspectType x -> InspectType
forall x. InspectType -> Rep InspectType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InspectType -> Rep InspectType x
from :: forall x. InspectType -> Rep InspectType x
$cto :: forall x. Rep InspectType x -> InspectType
to :: forall x. Rep InspectType x -> InspectType
Generic, ReadPrec [InspectType]
ReadPrec InspectType
Int -> ReadS InspectType
ReadS [InspectType]
(Int -> ReadS InspectType)
-> ReadS [InspectType]
-> ReadPrec InspectType
-> ReadPrec [InspectType]
-> Read InspectType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InspectType
readsPrec :: Int -> ReadS InspectType
$creadList :: ReadS [InspectType]
readList :: ReadS [InspectType]
$creadPrec :: ReadPrec InspectType
readPrec :: ReadPrec InspectType
$creadListPrec :: ReadPrec [InspectType]
readListPrec :: ReadPrec [InspectType]
Read)
data CallOpt = LegacyOpts [C.CallOption]
| CallPredicate [Pre]
| CallOnDates DatePattern [Pre]
deriving (Int -> CallOpt -> String -> String
[CallOpt] -> String -> String
CallOpt -> String
(Int -> CallOpt -> String -> String)
-> (CallOpt -> String)
-> ([CallOpt] -> String -> String)
-> Show CallOpt
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CallOpt -> String -> String
showsPrec :: Int -> CallOpt -> String -> String
$cshow :: CallOpt -> String
show :: CallOpt -> String
$cshowList :: [CallOpt] -> String -> String
showList :: [CallOpt] -> String -> String
Show, (forall x. CallOpt -> Rep CallOpt x)
-> (forall x. Rep CallOpt x -> CallOpt) -> Generic CallOpt
forall x. Rep CallOpt x -> CallOpt
forall x. CallOpt -> Rep CallOpt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CallOpt -> Rep CallOpt x
from :: forall x. CallOpt -> Rep CallOpt x
$cto :: forall x. Rep CallOpt x -> CallOpt
to :: forall x. Rep CallOpt x -> CallOpt
Generic, ReadPrec [CallOpt]
ReadPrec CallOpt
Int -> ReadS CallOpt
ReadS [CallOpt]
(Int -> ReadS CallOpt)
-> ReadS [CallOpt]
-> ReadPrec CallOpt
-> ReadPrec [CallOpt]
-> Read CallOpt
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CallOpt
readsPrec :: Int -> ReadS CallOpt
$creadList :: ReadS [CallOpt]
readList :: ReadS [CallOpt]
$creadPrec :: ReadPrec CallOpt
readPrec :: ReadPrec CallOpt
$creadListPrec :: ReadPrec [CallOpt]
readListPrec :: ReadPrec [CallOpt]
Read, Eq CallOpt
Eq CallOpt =>
(CallOpt -> CallOpt -> Ordering)
-> (CallOpt -> CallOpt -> Bool)
-> (CallOpt -> CallOpt -> Bool)
-> (CallOpt -> CallOpt -> Bool)
-> (CallOpt -> CallOpt -> Bool)
-> (CallOpt -> CallOpt -> CallOpt)
-> (CallOpt -> CallOpt -> CallOpt)
-> Ord CallOpt
CallOpt -> CallOpt -> Bool
CallOpt -> CallOpt -> Ordering
CallOpt -> CallOpt -> CallOpt
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 :: CallOpt -> CallOpt -> Ordering
compare :: CallOpt -> CallOpt -> Ordering
$c< :: CallOpt -> CallOpt -> Bool
< :: CallOpt -> CallOpt -> Bool
$c<= :: CallOpt -> CallOpt -> Bool
<= :: CallOpt -> CallOpt -> Bool
$c> :: CallOpt -> CallOpt -> Bool
> :: CallOpt -> CallOpt -> Bool
$c>= :: CallOpt -> CallOpt -> Bool
>= :: CallOpt -> CallOpt -> Bool
$cmax :: CallOpt -> CallOpt -> CallOpt
max :: CallOpt -> CallOpt -> CallOpt
$cmin :: CallOpt -> CallOpt -> CallOpt
min :: CallOpt -> CallOpt -> CallOpt
Ord, CallOpt -> CallOpt -> Bool
(CallOpt -> CallOpt -> Bool)
-> (CallOpt -> CallOpt -> Bool) -> Eq CallOpt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CallOpt -> CallOpt -> Bool
== :: CallOpt -> CallOpt -> Bool
$c/= :: CallOpt -> CallOpt -> Bool
/= :: CallOpt -> CallOpt -> Bool
Eq)
data StopBy = StopByDate Date
| StopByPre DatePattern [Pre]
deriving (Int -> StopBy -> String -> String
[StopBy] -> String -> String
StopBy -> String
(Int -> StopBy -> String -> String)
-> (StopBy -> String)
-> ([StopBy] -> String -> String)
-> Show StopBy
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> StopBy -> String -> String
showsPrec :: Int -> StopBy -> String -> String
$cshow :: StopBy -> String
show :: StopBy -> String
$cshowList :: [StopBy] -> String -> String
showList :: [StopBy] -> String -> String
Show, (forall x. StopBy -> Rep StopBy x)
-> (forall x. Rep StopBy x -> StopBy) -> Generic StopBy
forall x. Rep StopBy x -> StopBy
forall x. StopBy -> Rep StopBy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StopBy -> Rep StopBy x
from :: forall x. StopBy -> Rep StopBy x
$cto :: forall x. Rep StopBy x -> StopBy
to :: forall x. Rep StopBy x -> StopBy
Generic, ReadPrec [StopBy]
ReadPrec StopBy
Int -> ReadS StopBy
ReadS [StopBy]
(Int -> ReadS StopBy)
-> ReadS [StopBy]
-> ReadPrec StopBy
-> ReadPrec [StopBy]
-> Read StopBy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StopBy
readsPrec :: Int -> ReadS StopBy
$creadList :: ReadS [StopBy]
readList :: ReadS [StopBy]
$creadPrec :: ReadPrec StopBy
readPrec :: ReadPrec StopBy
$creadListPrec :: ReadPrec [StopBy]
readListPrec :: ReadPrec [StopBy]
Read)
data NonPerfAssumption = NonPerfAssumption {
NonPerfAssumption -> Maybe StopBy
stopRunBy :: Maybe StopBy
,NonPerfAssumption -> Maybe [(String, Ts)]
projectedExpense :: Maybe [(FeeName,Ts)]
,NonPerfAssumption -> Maybe [CallOpt]
callWhen :: Maybe [CallOpt]
,NonPerfAssumption -> Maybe RevolvingAssumption
revolving :: Maybe RevolvingAssumption
,NonPerfAssumption -> Maybe [RateAssumption]
interest :: Maybe [RateAssumption]
,NonPerfAssumption -> Maybe [InspectType]
inspectOn :: Maybe [InspectType]
,NonPerfAssumption -> Maybe DatePattern
buildFinancialReport :: Maybe DatePattern
,NonPerfAssumption -> Maybe BondPricingInput
pricing :: Maybe BondPricingInput
,NonPerfAssumption -> Maybe [(Date, DealCycle, String)]
fireTrigger :: Maybe [(Date,DealCycle,String)]
,NonPerfAssumption -> Maybe (Date, IRate, Table Float IRate)
makeWholeWhen :: Maybe (Date,Spread,Table Float Spread)
,NonPerfAssumption -> Maybe [TsPoint IssueBondEvent]
issueBondSchedule :: Maybe [TsPoint IssueBondEvent]
,NonPerfAssumption -> Maybe [TsPoint RefiEvent]
refinance :: Maybe [TsPoint RefiEvent]
} deriving (Int -> NonPerfAssumption -> String -> String
[NonPerfAssumption] -> String -> String
NonPerfAssumption -> String
(Int -> NonPerfAssumption -> String -> String)
-> (NonPerfAssumption -> String)
-> ([NonPerfAssumption] -> String -> String)
-> Show NonPerfAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> NonPerfAssumption -> String -> String
showsPrec :: Int -> NonPerfAssumption -> String -> String
$cshow :: NonPerfAssumption -> String
show :: NonPerfAssumption -> String
$cshowList :: [NonPerfAssumption] -> String -> String
showList :: [NonPerfAssumption] -> String -> String
Show, (forall x. NonPerfAssumption -> Rep NonPerfAssumption x)
-> (forall x. Rep NonPerfAssumption x -> NonPerfAssumption)
-> Generic NonPerfAssumption
forall x. Rep NonPerfAssumption x -> NonPerfAssumption
forall x. NonPerfAssumption -> Rep NonPerfAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NonPerfAssumption -> Rep NonPerfAssumption x
from :: forall x. NonPerfAssumption -> Rep NonPerfAssumption x
$cto :: forall x. Rep NonPerfAssumption x -> NonPerfAssumption
to :: forall x. Rep NonPerfAssumption x -> NonPerfAssumption
Generic)
data AssumptionInput = Single ApplyAssumptionType NonPerfAssumption
| Multiple (Map.Map String ApplyAssumptionType) NonPerfAssumption
deriving (Int -> AssumptionInput -> String -> String
[AssumptionInput] -> String -> String
AssumptionInput -> String
(Int -> AssumptionInput -> String -> String)
-> (AssumptionInput -> String)
-> ([AssumptionInput] -> String -> String)
-> Show AssumptionInput
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssumptionInput -> String -> String
showsPrec :: Int -> AssumptionInput -> String -> String
$cshow :: AssumptionInput -> String
show :: AssumptionInput -> String
$cshowList :: [AssumptionInput] -> String -> String
showList :: [AssumptionInput] -> String -> String
Show,(forall x. AssumptionInput -> Rep AssumptionInput x)
-> (forall x. Rep AssumptionInput x -> AssumptionInput)
-> Generic AssumptionInput
forall x. Rep AssumptionInput x -> AssumptionInput
forall x. AssumptionInput -> Rep AssumptionInput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssumptionInput -> Rep AssumptionInput x
from :: forall x. AssumptionInput -> Rep AssumptionInput x
$cto :: forall x. Rep AssumptionInput x -> AssumptionInput
to :: forall x. Rep AssumptionInput x -> AssumptionInput
Generic)
data AssetDefaultAssumption = DefaultConstant Rate
| DefaultCDR Rate
| DefaultVec [Rate]
| DefaultVecPadding [Rate]
| DefaultByAmt (Balance,[Rate])
| DefaultAtEnd
| DefaultAtEndByRate Rate Rate
| DefaultStressByTs Ts AssetDefaultAssumption
| DefaultByTerm [[Rate]]
deriving (Int -> AssetDefaultAssumption -> String -> String
[AssetDefaultAssumption] -> String -> String
AssetDefaultAssumption -> String
(Int -> AssetDefaultAssumption -> String -> String)
-> (AssetDefaultAssumption -> String)
-> ([AssetDefaultAssumption] -> String -> String)
-> Show AssetDefaultAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssetDefaultAssumption -> String -> String
showsPrec :: Int -> AssetDefaultAssumption -> String -> String
$cshow :: AssetDefaultAssumption -> String
show :: AssetDefaultAssumption -> String
$cshowList :: [AssetDefaultAssumption] -> String -> String
showList :: [AssetDefaultAssumption] -> String -> String
Show,(forall x. AssetDefaultAssumption -> Rep AssetDefaultAssumption x)
-> (forall x.
Rep AssetDefaultAssumption x -> AssetDefaultAssumption)
-> Generic AssetDefaultAssumption
forall x. Rep AssetDefaultAssumption x -> AssetDefaultAssumption
forall x. AssetDefaultAssumption -> Rep AssetDefaultAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssetDefaultAssumption -> Rep AssetDefaultAssumption x
from :: forall x. AssetDefaultAssumption -> Rep AssetDefaultAssumption x
$cto :: forall x. Rep AssetDefaultAssumption x -> AssetDefaultAssumption
to :: forall x. Rep AssetDefaultAssumption x -> AssetDefaultAssumption
Generic,ReadPrec [AssetDefaultAssumption]
ReadPrec AssetDefaultAssumption
Int -> ReadS AssetDefaultAssumption
ReadS [AssetDefaultAssumption]
(Int -> ReadS AssetDefaultAssumption)
-> ReadS [AssetDefaultAssumption]
-> ReadPrec AssetDefaultAssumption
-> ReadPrec [AssetDefaultAssumption]
-> Read AssetDefaultAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssetDefaultAssumption
readsPrec :: Int -> ReadS AssetDefaultAssumption
$creadList :: ReadS [AssetDefaultAssumption]
readList :: ReadS [AssetDefaultAssumption]
$creadPrec :: ReadPrec AssetDefaultAssumption
readPrec :: ReadPrec AssetDefaultAssumption
$creadListPrec :: ReadPrec [AssetDefaultAssumption]
readListPrec :: ReadPrec [AssetDefaultAssumption]
Read)
stressDefaultAssump :: Rate -> AssetDefaultAssumption -> AssetDefaultAssumption
stressDefaultAssump :: Rate -> AssetDefaultAssumption -> AssetDefaultAssumption
stressDefaultAssump Rate
x (DefaultConstant Rate
r) = Rate -> AssetDefaultAssumption
DefaultConstant (Rate -> AssetDefaultAssumption) -> Rate -> AssetDefaultAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
rRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x)
stressDefaultAssump Rate
x (DefaultCDR Rate
r) = Rate -> AssetDefaultAssumption
DefaultCDR (Rate -> AssetDefaultAssumption) -> Rate -> AssetDefaultAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
rRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x)
stressDefaultAssump Rate
x (DefaultVec [Rate]
rs) = [Rate] -> AssetDefaultAssumption
DefaultVec ([Rate] -> AssetDefaultAssumption)
-> [Rate] -> AssetDefaultAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0 ((Rate
xRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*) (Rate -> Rate) -> [Rate] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
rs)
stressDefaultAssump Rate
x (DefaultVecPadding [Rate]
rs) = [Rate] -> AssetDefaultAssumption
DefaultVecPadding ([Rate] -> AssetDefaultAssumption)
-> [Rate] -> AssetDefaultAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0 ((Rate
xRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*) (Rate -> Rate) -> [Rate] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
rs)
stressDefaultAssump Rate
x (DefaultByAmt (Balance
b,[Rate]
rs)) = (Balance, [Rate]) -> AssetDefaultAssumption
DefaultByAmt (Balance -> Rate -> Balance
mulBR Balance
b Rate
x, [Rate]
rs)
stressDefaultAssump Rate
x (DefaultAtEndByRate Rate
r1 Rate
r2) = Rate -> Rate -> AssetDefaultAssumption
DefaultAtEndByRate (Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
r1Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x)) (Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
r2Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x))
stressDefaultAssump Rate
x (DefaultStressByTs Ts
ts AssetDefaultAssumption
a) = Ts -> AssetDefaultAssumption -> AssetDefaultAssumption
DefaultStressByTs Ts
ts (Rate -> AssetDefaultAssumption -> AssetDefaultAssumption
stressDefaultAssump Rate
x AssetDefaultAssumption
a)
stressDefaultAssump Rate
x (DefaultByTerm [[Rate]]
rss) = [[Rate]] -> AssetDefaultAssumption
DefaultByTerm ([[Rate]] -> AssetDefaultAssumption)
-> [[Rate]] -> AssetDefaultAssumption
forall a b. (a -> b) -> a -> b
$ ((Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0) ([Rate] -> [Rate]) -> [[Rate]] -> [[Rate]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (([Rate] -> [Rate]) -> [[Rate]] -> [[Rate]]
forall a b. (a -> b) -> [a] -> [b]
map ((Rate -> Rate) -> [Rate] -> [Rate]
forall a b. (a -> b) -> [a] -> [b]
map (Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
x)) [[Rate]]
rss))
stressPrepaymentAssump :: Rate -> AssetPrepayAssumption -> AssetPrepayAssumption
stressPrepaymentAssump :: Rate -> AssetPrepayAssumption -> AssetPrepayAssumption
stressPrepaymentAssump Rate
x (PrepaymentConstant Rate
r) = Rate -> AssetPrepayAssumption
PrepaymentConstant (Rate -> AssetPrepayAssumption) -> Rate -> AssetPrepayAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
rRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x)
stressPrepaymentAssump Rate
x (PrepaymentCPR Rate
r) = Rate -> AssetPrepayAssumption
PrepaymentCPR (Rate -> AssetPrepayAssumption) -> Rate -> AssetPrepayAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
rRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x)
stressPrepaymentAssump Rate
x (PrepaymentVec [Rate]
rs) = [Rate] -> AssetPrepayAssumption
PrepaymentVec ([Rate] -> AssetPrepayAssumption)
-> [Rate] -> AssetPrepayAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0 ((Rate
xRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*) (Rate -> Rate) -> [Rate] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
rs)
stressPrepaymentAssump Rate
x (PrepaymentVecPadding [Rate]
rs) = [Rate] -> AssetPrepayAssumption
PrepaymentVecPadding ([Rate] -> AssetPrepayAssumption)
-> [Rate] -> AssetPrepayAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0 ((Rate
xRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*) (Rate -> Rate) -> [Rate] -> [Rate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
rs)
stressPrepaymentAssump Rate
x (PrepayByAmt (Balance
b,[Rate]
rs)) = (Balance, [Rate]) -> AssetPrepayAssumption
PrepayByAmt (Balance -> Rate -> Balance
mulBR Balance
b Rate
x, [Rate]
rs)
stressPrepaymentAssump Rate
x (PrepayStressByTs Ts
ts AssetPrepayAssumption
a) = Ts -> AssetPrepayAssumption -> AssetPrepayAssumption
PrepayStressByTs Ts
ts (Rate -> AssetPrepayAssumption -> AssetPrepayAssumption
stressPrepaymentAssump Rate
x AssetPrepayAssumption
a)
stressPrepaymentAssump Rate
x (PrepaymentPSA Rate
r) = Rate -> AssetPrepayAssumption
PrepaymentPSA (Rate -> AssetPrepayAssumption) -> Rate -> AssetPrepayAssumption
forall a b. (a -> b) -> a -> b
$ Rate -> Rate -> Rate
forall a. Ord a => a -> a -> a
min Rate
1.0 (Rate
rRate -> Rate -> Rate
forall a. Num a => a -> a -> a
*Rate
x)
stressPrepaymentAssump Rate
x (PrepaymentByTerm [[Rate]]
rss) = [[Rate]] -> AssetPrepayAssumption
PrepaymentByTerm ([[Rate]] -> AssetPrepayAssumption)
-> [[Rate]] -> AssetPrepayAssumption
forall a b. (a -> b) -> a -> b
$ (Rate -> [Rate] -> [Rate]
forall a. Ord a => a -> [a] -> [a]
capWith Rate
1.0 ([Rate] -> [Rate]) -> [[Rate]] -> [[Rate]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (([Rate] -> [Rate]) -> [[Rate]] -> [[Rate]]
forall a b. (a -> b) -> [a] -> [b]
map ((Rate -> Rate) -> [Rate] -> [Rate]
forall a b. (a -> b) -> [a] -> [b]
map (Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
x)) [[Rate]]
rss))
data AssetPrepayAssumption = PrepaymentConstant Rate
| PrepaymentCPR Rate
| PrepaymentVec [Rate]
| PrepaymentVecPadding [Rate]
| PrepayByAmt (Balance,[Rate])
| PrepayStressByTs Ts AssetPrepayAssumption
| PrepaymentPSA Rate
| PrepaymentByTerm [[Rate]]
deriving (Int -> AssetPrepayAssumption -> String -> String
[AssetPrepayAssumption] -> String -> String
AssetPrepayAssumption -> String
(Int -> AssetPrepayAssumption -> String -> String)
-> (AssetPrepayAssumption -> String)
-> ([AssetPrepayAssumption] -> String -> String)
-> Show AssetPrepayAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssetPrepayAssumption -> String -> String
showsPrec :: Int -> AssetPrepayAssumption -> String -> String
$cshow :: AssetPrepayAssumption -> String
show :: AssetPrepayAssumption -> String
$cshowList :: [AssetPrepayAssumption] -> String -> String
showList :: [AssetPrepayAssumption] -> String -> String
Show,(forall x. AssetPrepayAssumption -> Rep AssetPrepayAssumption x)
-> (forall x. Rep AssetPrepayAssumption x -> AssetPrepayAssumption)
-> Generic AssetPrepayAssumption
forall x. Rep AssetPrepayAssumption x -> AssetPrepayAssumption
forall x. AssetPrepayAssumption -> Rep AssetPrepayAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssetPrepayAssumption -> Rep AssetPrepayAssumption x
from :: forall x. AssetPrepayAssumption -> Rep AssetPrepayAssumption x
$cto :: forall x. Rep AssetPrepayAssumption x -> AssetPrepayAssumption
to :: forall x. Rep AssetPrepayAssumption x -> AssetPrepayAssumption
Generic,ReadPrec [AssetPrepayAssumption]
ReadPrec AssetPrepayAssumption
Int -> ReadS AssetPrepayAssumption
ReadS [AssetPrepayAssumption]
(Int -> ReadS AssetPrepayAssumption)
-> ReadS [AssetPrepayAssumption]
-> ReadPrec AssetPrepayAssumption
-> ReadPrec [AssetPrepayAssumption]
-> Read AssetPrepayAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssetPrepayAssumption
readsPrec :: Int -> ReadS AssetPrepayAssumption
$creadList :: ReadS [AssetPrepayAssumption]
readList :: ReadS [AssetPrepayAssumption]
$creadPrec :: ReadPrec AssetPrepayAssumption
readPrec :: ReadPrec AssetPrepayAssumption
$creadListPrec :: ReadPrec [AssetPrepayAssumption]
readListPrec :: ReadPrec [AssetPrepayAssumption]
Read)
data AssetDelinquencyAssumption = DelinqCDR Rate (Lag,Rate)
| DelinqByAmt (Balance,[Rate]) (Lag,Rate)
| Dummy3
deriving (Int -> AssetDelinquencyAssumption -> String -> String
[AssetDelinquencyAssumption] -> String -> String
AssetDelinquencyAssumption -> String
(Int -> AssetDelinquencyAssumption -> String -> String)
-> (AssetDelinquencyAssumption -> String)
-> ([AssetDelinquencyAssumption] -> String -> String)
-> Show AssetDelinquencyAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssetDelinquencyAssumption -> String -> String
showsPrec :: Int -> AssetDelinquencyAssumption -> String -> String
$cshow :: AssetDelinquencyAssumption -> String
show :: AssetDelinquencyAssumption -> String
$cshowList :: [AssetDelinquencyAssumption] -> String -> String
showList :: [AssetDelinquencyAssumption] -> String -> String
Show,(forall x.
AssetDelinquencyAssumption -> Rep AssetDelinquencyAssumption x)
-> (forall x.
Rep AssetDelinquencyAssumption x -> AssetDelinquencyAssumption)
-> Generic AssetDelinquencyAssumption
forall x.
Rep AssetDelinquencyAssumption x -> AssetDelinquencyAssumption
forall x.
AssetDelinquencyAssumption -> Rep AssetDelinquencyAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
AssetDelinquencyAssumption -> Rep AssetDelinquencyAssumption x
from :: forall x.
AssetDelinquencyAssumption -> Rep AssetDelinquencyAssumption x
$cto :: forall x.
Rep AssetDelinquencyAssumption x -> AssetDelinquencyAssumption
to :: forall x.
Rep AssetDelinquencyAssumption x -> AssetDelinquencyAssumption
Generic,ReadPrec [AssetDelinquencyAssumption]
ReadPrec AssetDelinquencyAssumption
Int -> ReadS AssetDelinquencyAssumption
ReadS [AssetDelinquencyAssumption]
(Int -> ReadS AssetDelinquencyAssumption)
-> ReadS [AssetDelinquencyAssumption]
-> ReadPrec AssetDelinquencyAssumption
-> ReadPrec [AssetDelinquencyAssumption]
-> Read AssetDelinquencyAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssetDelinquencyAssumption
readsPrec :: Int -> ReadS AssetDelinquencyAssumption
$creadList :: ReadS [AssetDelinquencyAssumption]
readList :: ReadS [AssetDelinquencyAssumption]
$creadPrec :: ReadPrec AssetDelinquencyAssumption
readPrec :: ReadPrec AssetDelinquencyAssumption
$creadListPrec :: ReadPrec [AssetDelinquencyAssumption]
readListPrec :: ReadPrec [AssetDelinquencyAssumption]
Read)
data RecoveryAssumption = Recovery (Rate,Int)
| RecoveryTiming (Rate,[Rate])
| RecoveryByDays Rate [(Int, Rate)]
deriving (Int -> RecoveryAssumption -> String -> String
[RecoveryAssumption] -> String -> String
RecoveryAssumption -> String
(Int -> RecoveryAssumption -> String -> String)
-> (RecoveryAssumption -> String)
-> ([RecoveryAssumption] -> String -> String)
-> Show RecoveryAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RecoveryAssumption -> String -> String
showsPrec :: Int -> RecoveryAssumption -> String -> String
$cshow :: RecoveryAssumption -> String
show :: RecoveryAssumption -> String
$cshowList :: [RecoveryAssumption] -> String -> String
showList :: [RecoveryAssumption] -> String -> String
Show,(forall x. RecoveryAssumption -> Rep RecoveryAssumption x)
-> (forall x. Rep RecoveryAssumption x -> RecoveryAssumption)
-> Generic RecoveryAssumption
forall x. Rep RecoveryAssumption x -> RecoveryAssumption
forall x. RecoveryAssumption -> Rep RecoveryAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RecoveryAssumption -> Rep RecoveryAssumption x
from :: forall x. RecoveryAssumption -> Rep RecoveryAssumption x
$cto :: forall x. Rep RecoveryAssumption x -> RecoveryAssumption
to :: forall x. Rep RecoveryAssumption x -> RecoveryAssumption
Generic,ReadPrec [RecoveryAssumption]
ReadPrec RecoveryAssumption
Int -> ReadS RecoveryAssumption
ReadS [RecoveryAssumption]
(Int -> ReadS RecoveryAssumption)
-> ReadS [RecoveryAssumption]
-> ReadPrec RecoveryAssumption
-> ReadPrec [RecoveryAssumption]
-> Read RecoveryAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RecoveryAssumption
readsPrec :: Int -> ReadS RecoveryAssumption
$creadList :: ReadS [RecoveryAssumption]
readList :: ReadS [RecoveryAssumption]
$creadPrec :: ReadPrec RecoveryAssumption
readPrec :: ReadPrec RecoveryAssumption
$creadListPrec :: ReadPrec [RecoveryAssumption]
readListPrec :: ReadPrec [RecoveryAssumption]
Read)
data LeaseAssetGapAssump = GapDays Int
| GapDaysByCurve Ts
deriving (Int -> LeaseAssetGapAssump -> String -> String
[LeaseAssetGapAssump] -> String -> String
LeaseAssetGapAssump -> String
(Int -> LeaseAssetGapAssump -> String -> String)
-> (LeaseAssetGapAssump -> String)
-> ([LeaseAssetGapAssump] -> String -> String)
-> Show LeaseAssetGapAssump
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LeaseAssetGapAssump -> String -> String
showsPrec :: Int -> LeaseAssetGapAssump -> String -> String
$cshow :: LeaseAssetGapAssump -> String
show :: LeaseAssetGapAssump -> String
$cshowList :: [LeaseAssetGapAssump] -> String -> String
showList :: [LeaseAssetGapAssump] -> String -> String
Show,(forall x. LeaseAssetGapAssump -> Rep LeaseAssetGapAssump x)
-> (forall x. Rep LeaseAssetGapAssump x -> LeaseAssetGapAssump)
-> Generic LeaseAssetGapAssump
forall x. Rep LeaseAssetGapAssump x -> LeaseAssetGapAssump
forall x. LeaseAssetGapAssump -> Rep LeaseAssetGapAssump x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LeaseAssetGapAssump -> Rep LeaseAssetGapAssump x
from :: forall x. LeaseAssetGapAssump -> Rep LeaseAssetGapAssump x
$cto :: forall x. Rep LeaseAssetGapAssump x -> LeaseAssetGapAssump
to :: forall x. Rep LeaseAssetGapAssump x -> LeaseAssetGapAssump
Generic,ReadPrec [LeaseAssetGapAssump]
ReadPrec LeaseAssetGapAssump
Int -> ReadS LeaseAssetGapAssump
ReadS [LeaseAssetGapAssump]
(Int -> ReadS LeaseAssetGapAssump)
-> ReadS [LeaseAssetGapAssump]
-> ReadPrec LeaseAssetGapAssump
-> ReadPrec [LeaseAssetGapAssump]
-> Read LeaseAssetGapAssump
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LeaseAssetGapAssump
readsPrec :: Int -> ReadS LeaseAssetGapAssump
$creadList :: ReadS [LeaseAssetGapAssump]
readList :: ReadS [LeaseAssetGapAssump]
$creadPrec :: ReadPrec LeaseAssetGapAssump
readPrec :: ReadPrec LeaseAssetGapAssump
$creadListPrec :: ReadPrec [LeaseAssetGapAssump]
readListPrec :: ReadPrec [LeaseAssetGapAssump]
Read)
data LeaseAssetRentAssump = BaseAnnualRate Rate
| BaseCurve Ts
| BaseByVec [Rate]
deriving (Int -> LeaseAssetRentAssump -> String -> String
[LeaseAssetRentAssump] -> String -> String
LeaseAssetRentAssump -> String
(Int -> LeaseAssetRentAssump -> String -> String)
-> (LeaseAssetRentAssump -> String)
-> ([LeaseAssetRentAssump] -> String -> String)
-> Show LeaseAssetRentAssump
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LeaseAssetRentAssump -> String -> String
showsPrec :: Int -> LeaseAssetRentAssump -> String -> String
$cshow :: LeaseAssetRentAssump -> String
show :: LeaseAssetRentAssump -> String
$cshowList :: [LeaseAssetRentAssump] -> String -> String
showList :: [LeaseAssetRentAssump] -> String -> String
Show,(forall x. LeaseAssetRentAssump -> Rep LeaseAssetRentAssump x)
-> (forall x. Rep LeaseAssetRentAssump x -> LeaseAssetRentAssump)
-> Generic LeaseAssetRentAssump
forall x. Rep LeaseAssetRentAssump x -> LeaseAssetRentAssump
forall x. LeaseAssetRentAssump -> Rep LeaseAssetRentAssump x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LeaseAssetRentAssump -> Rep LeaseAssetRentAssump x
from :: forall x. LeaseAssetRentAssump -> Rep LeaseAssetRentAssump x
$cto :: forall x. Rep LeaseAssetRentAssump x -> LeaseAssetRentAssump
to :: forall x. Rep LeaseAssetRentAssump x -> LeaseAssetRentAssump
Generic,ReadPrec [LeaseAssetRentAssump]
ReadPrec LeaseAssetRentAssump
Int -> ReadS LeaseAssetRentAssump
ReadS [LeaseAssetRentAssump]
(Int -> ReadS LeaseAssetRentAssump)
-> ReadS [LeaseAssetRentAssump]
-> ReadPrec LeaseAssetRentAssump
-> ReadPrec [LeaseAssetRentAssump]
-> Read LeaseAssetRentAssump
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LeaseAssetRentAssump
readsPrec :: Int -> ReadS LeaseAssetRentAssump
$creadList :: ReadS [LeaseAssetRentAssump]
readList :: ReadS [LeaseAssetRentAssump]
$creadPrec :: ReadPrec LeaseAssetRentAssump
readPrec :: ReadPrec LeaseAssetRentAssump
$creadListPrec :: ReadPrec [LeaseAssetRentAssump]
readListPrec :: ReadPrec [LeaseAssetRentAssump]
Read)
data LeaseDefaultType = DefaultByContinuation Rate
| DefaultByTermination Rate
deriving (Int -> LeaseDefaultType -> String -> String
[LeaseDefaultType] -> String -> String
LeaseDefaultType -> String
(Int -> LeaseDefaultType -> String -> String)
-> (LeaseDefaultType -> String)
-> ([LeaseDefaultType] -> String -> String)
-> Show LeaseDefaultType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LeaseDefaultType -> String -> String
showsPrec :: Int -> LeaseDefaultType -> String -> String
$cshow :: LeaseDefaultType -> String
show :: LeaseDefaultType -> String
$cshowList :: [LeaseDefaultType] -> String -> String
showList :: [LeaseDefaultType] -> String -> String
Show,(forall x. LeaseDefaultType -> Rep LeaseDefaultType x)
-> (forall x. Rep LeaseDefaultType x -> LeaseDefaultType)
-> Generic LeaseDefaultType
forall x. Rep LeaseDefaultType x -> LeaseDefaultType
forall x. LeaseDefaultType -> Rep LeaseDefaultType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LeaseDefaultType -> Rep LeaseDefaultType x
from :: forall x. LeaseDefaultType -> Rep LeaseDefaultType x
$cto :: forall x. Rep LeaseDefaultType x -> LeaseDefaultType
to :: forall x. Rep LeaseDefaultType x -> LeaseDefaultType
Generic,ReadPrec [LeaseDefaultType]
ReadPrec LeaseDefaultType
Int -> ReadS LeaseDefaultType
ReadS [LeaseDefaultType]
(Int -> ReadS LeaseDefaultType)
-> ReadS [LeaseDefaultType]
-> ReadPrec LeaseDefaultType
-> ReadPrec [LeaseDefaultType]
-> Read LeaseDefaultType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LeaseDefaultType
readsPrec :: Int -> ReadS LeaseDefaultType
$creadList :: ReadS [LeaseDefaultType]
readList :: ReadS [LeaseDefaultType]
$creadPrec :: ReadPrec LeaseDefaultType
readPrec :: ReadPrec LeaseDefaultType
$creadListPrec :: ReadPrec [LeaseDefaultType]
readListPrec :: ReadPrec [LeaseDefaultType]
Read)
data LeaseEndType = CutByDate Date
| StopByExtTimes Int
| EarlierOf Date Int
| LaterOf Date Int
deriving (Int -> LeaseEndType -> String -> String
[LeaseEndType] -> String -> String
LeaseEndType -> String
(Int -> LeaseEndType -> String -> String)
-> (LeaseEndType -> String)
-> ([LeaseEndType] -> String -> String)
-> Show LeaseEndType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LeaseEndType -> String -> String
showsPrec :: Int -> LeaseEndType -> String -> String
$cshow :: LeaseEndType -> String
show :: LeaseEndType -> String
$cshowList :: [LeaseEndType] -> String -> String
showList :: [LeaseEndType] -> String -> String
Show,(forall x. LeaseEndType -> Rep LeaseEndType x)
-> (forall x. Rep LeaseEndType x -> LeaseEndType)
-> Generic LeaseEndType
forall x. Rep LeaseEndType x -> LeaseEndType
forall x. LeaseEndType -> Rep LeaseEndType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LeaseEndType -> Rep LeaseEndType x
from :: forall x. LeaseEndType -> Rep LeaseEndType x
$cto :: forall x. Rep LeaseEndType x -> LeaseEndType
to :: forall x. Rep LeaseEndType x -> LeaseEndType
Generic,ReadPrec [LeaseEndType]
ReadPrec LeaseEndType
Int -> ReadS LeaseEndType
ReadS [LeaseEndType]
(Int -> ReadS LeaseEndType)
-> ReadS [LeaseEndType]
-> ReadPrec LeaseEndType
-> ReadPrec [LeaseEndType]
-> Read LeaseEndType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LeaseEndType
readsPrec :: Int -> ReadS LeaseEndType
$creadList :: ReadS [LeaseEndType]
readList :: ReadS [LeaseEndType]
$creadPrec :: ReadPrec LeaseEndType
readPrec :: ReadPrec LeaseEndType
$creadListPrec :: ReadPrec [LeaseEndType]
readListPrec :: ReadPrec [LeaseEndType]
Read)
data = {
ExtraStress -> Maybe Ts
defaultFactors :: Maybe Ts
,ExtraStress -> Maybe Ts
prepaymentFactors :: Maybe Ts
,ExtraStress -> Maybe [(PoolSource, Rate)]
poolHairCut :: Maybe [(PoolSource, Rate)]
} deriving (Int -> ExtraStress -> String -> String
[ExtraStress] -> String -> String
ExtraStress -> String
(Int -> ExtraStress -> String -> String)
-> (ExtraStress -> String)
-> ([ExtraStress] -> String -> String)
-> Show ExtraStress
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ExtraStress -> String -> String
showsPrec :: Int -> ExtraStress -> String -> String
$cshow :: ExtraStress -> String
show :: ExtraStress -> String
$cshowList :: [ExtraStress] -> String -> String
showList :: [ExtraStress] -> String -> String
Show,(forall x. ExtraStress -> Rep ExtraStress x)
-> (forall x. Rep ExtraStress x -> ExtraStress)
-> Generic ExtraStress
forall x. Rep ExtraStress x -> ExtraStress
forall x. ExtraStress -> Rep ExtraStress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExtraStress -> Rep ExtraStress x
from :: forall x. ExtraStress -> Rep ExtraStress x
$cto :: forall x. Rep ExtraStress x -> ExtraStress
to :: forall x. Rep ExtraStress x -> ExtraStress
Generic,ReadPrec [ExtraStress]
ReadPrec ExtraStress
Int -> ReadS ExtraStress
ReadS [ExtraStress]
(Int -> ReadS ExtraStress)
-> ReadS [ExtraStress]
-> ReadPrec ExtraStress
-> ReadPrec [ExtraStress]
-> Read ExtraStress
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExtraStress
readsPrec :: Int -> ReadS ExtraStress
$creadList :: ReadS [ExtraStress]
readList :: ReadS [ExtraStress]
$creadPrec :: ReadPrec ExtraStress
readPrec :: ReadPrec ExtraStress
$creadListPrec :: ReadPrec [ExtraStress]
readListPrec :: ReadPrec [ExtraStress]
Read)
type ExtendCashflowDates = DatePattern
data AssetDefaultedPerfAssumption = DefaultedRecovery Rate Int [Rate]
| DummyDefaultAssump
deriving (Int -> AssetDefaultedPerfAssumption -> String -> String
[AssetDefaultedPerfAssumption] -> String -> String
AssetDefaultedPerfAssumption -> String
(Int -> AssetDefaultedPerfAssumption -> String -> String)
-> (AssetDefaultedPerfAssumption -> String)
-> ([AssetDefaultedPerfAssumption] -> String -> String)
-> Show AssetDefaultedPerfAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssetDefaultedPerfAssumption -> String -> String
showsPrec :: Int -> AssetDefaultedPerfAssumption -> String -> String
$cshow :: AssetDefaultedPerfAssumption -> String
show :: AssetDefaultedPerfAssumption -> String
$cshowList :: [AssetDefaultedPerfAssumption] -> String -> String
showList :: [AssetDefaultedPerfAssumption] -> String -> String
Show,(forall x.
AssetDefaultedPerfAssumption -> Rep AssetDefaultedPerfAssumption x)
-> (forall x.
Rep AssetDefaultedPerfAssumption x -> AssetDefaultedPerfAssumption)
-> Generic AssetDefaultedPerfAssumption
forall x.
Rep AssetDefaultedPerfAssumption x -> AssetDefaultedPerfAssumption
forall x.
AssetDefaultedPerfAssumption -> Rep AssetDefaultedPerfAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
AssetDefaultedPerfAssumption -> Rep AssetDefaultedPerfAssumption x
from :: forall x.
AssetDefaultedPerfAssumption -> Rep AssetDefaultedPerfAssumption x
$cto :: forall x.
Rep AssetDefaultedPerfAssumption x -> AssetDefaultedPerfAssumption
to :: forall x.
Rep AssetDefaultedPerfAssumption x -> AssetDefaultedPerfAssumption
Generic,ReadPrec [AssetDefaultedPerfAssumption]
ReadPrec AssetDefaultedPerfAssumption
Int -> ReadS AssetDefaultedPerfAssumption
ReadS [AssetDefaultedPerfAssumption]
(Int -> ReadS AssetDefaultedPerfAssumption)
-> ReadS [AssetDefaultedPerfAssumption]
-> ReadPrec AssetDefaultedPerfAssumption
-> ReadPrec [AssetDefaultedPerfAssumption]
-> Read AssetDefaultedPerfAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssetDefaultedPerfAssumption
readsPrec :: Int -> ReadS AssetDefaultedPerfAssumption
$creadList :: ReadS [AssetDefaultedPerfAssumption]
readList :: ReadS [AssetDefaultedPerfAssumption]
$creadPrec :: ReadPrec AssetDefaultedPerfAssumption
readPrec :: ReadPrec AssetDefaultedPerfAssumption
$creadListPrec :: ReadPrec [AssetDefaultedPerfAssumption]
readListPrec :: ReadPrec [AssetDefaultedPerfAssumption]
Read)
data AssetDelinqPerfAssumption = DummyDelinqAssump
deriving (Int -> AssetDelinqPerfAssumption -> String -> String
[AssetDelinqPerfAssumption] -> String -> String
AssetDelinqPerfAssumption -> String
(Int -> AssetDelinqPerfAssumption -> String -> String)
-> (AssetDelinqPerfAssumption -> String)
-> ([AssetDelinqPerfAssumption] -> String -> String)
-> Show AssetDelinqPerfAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssetDelinqPerfAssumption -> String -> String
showsPrec :: Int -> AssetDelinqPerfAssumption -> String -> String
$cshow :: AssetDelinqPerfAssumption -> String
show :: AssetDelinqPerfAssumption -> String
$cshowList :: [AssetDelinqPerfAssumption] -> String -> String
showList :: [AssetDelinqPerfAssumption] -> String -> String
Show,(forall x.
AssetDelinqPerfAssumption -> Rep AssetDelinqPerfAssumption x)
-> (forall x.
Rep AssetDelinqPerfAssumption x -> AssetDelinqPerfAssumption)
-> Generic AssetDelinqPerfAssumption
forall x.
Rep AssetDelinqPerfAssumption x -> AssetDelinqPerfAssumption
forall x.
AssetDelinqPerfAssumption -> Rep AssetDelinqPerfAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
AssetDelinqPerfAssumption -> Rep AssetDelinqPerfAssumption x
from :: forall x.
AssetDelinqPerfAssumption -> Rep AssetDelinqPerfAssumption x
$cto :: forall x.
Rep AssetDelinqPerfAssumption x -> AssetDelinqPerfAssumption
to :: forall x.
Rep AssetDelinqPerfAssumption x -> AssetDelinqPerfAssumption
Generic,ReadPrec [AssetDelinqPerfAssumption]
ReadPrec AssetDelinqPerfAssumption
Int -> ReadS AssetDelinqPerfAssumption
ReadS [AssetDelinqPerfAssumption]
(Int -> ReadS AssetDelinqPerfAssumption)
-> ReadS [AssetDelinqPerfAssumption]
-> ReadPrec AssetDelinqPerfAssumption
-> ReadPrec [AssetDelinqPerfAssumption]
-> Read AssetDelinqPerfAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssetDelinqPerfAssumption
readsPrec :: Int -> ReadS AssetDelinqPerfAssumption
$creadList :: ReadS [AssetDelinqPerfAssumption]
readList :: ReadS [AssetDelinqPerfAssumption]
$creadPrec :: ReadPrec AssetDelinqPerfAssumption
readPrec :: ReadPrec AssetDelinqPerfAssumption
$creadListPrec :: ReadPrec [AssetDelinqPerfAssumption]
readListPrec :: ReadPrec [AssetDelinqPerfAssumption]
Read)
data AssetPerfAssumption = MortgageAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
| MortgageDeqAssump (Maybe AssetDelinquencyAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
| LeaseAssump (Maybe LeaseDefaultType) LeaseAssetGapAssump LeaseAssetRentAssump LeaseEndType
| LoanAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
| InstallmentAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
| ReceivableAssump (Maybe AssetDefaultAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
| FixedAssetAssump Ts Ts (Maybe Int)
deriving (Int -> AssetPerfAssumption -> String -> String
[AssetPerfAssumption] -> String -> String
AssetPerfAssumption -> String
(Int -> AssetPerfAssumption -> String -> String)
-> (AssetPerfAssumption -> String)
-> ([AssetPerfAssumption] -> String -> String)
-> Show AssetPerfAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssetPerfAssumption -> String -> String
showsPrec :: Int -> AssetPerfAssumption -> String -> String
$cshow :: AssetPerfAssumption -> String
show :: AssetPerfAssumption -> String
$cshowList :: [AssetPerfAssumption] -> String -> String
showList :: [AssetPerfAssumption] -> String -> String
Show,(forall x. AssetPerfAssumption -> Rep AssetPerfAssumption x)
-> (forall x. Rep AssetPerfAssumption x -> AssetPerfAssumption)
-> Generic AssetPerfAssumption
forall x. Rep AssetPerfAssumption x -> AssetPerfAssumption
forall x. AssetPerfAssumption -> Rep AssetPerfAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AssetPerfAssumption -> Rep AssetPerfAssumption x
from :: forall x. AssetPerfAssumption -> Rep AssetPerfAssumption x
$cto :: forall x. Rep AssetPerfAssumption x -> AssetPerfAssumption
to :: forall x. Rep AssetPerfAssumption x -> AssetPerfAssumption
Generic,ReadPrec [AssetPerfAssumption]
ReadPrec AssetPerfAssumption
Int -> ReadS AssetPerfAssumption
ReadS [AssetPerfAssumption]
(Int -> ReadS AssetPerfAssumption)
-> ReadS [AssetPerfAssumption]
-> ReadPrec AssetPerfAssumption
-> ReadPrec [AssetPerfAssumption]
-> Read AssetPerfAssumption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssetPerfAssumption
readsPrec :: Int -> ReadS AssetPerfAssumption
$creadList :: ReadS [AssetPerfAssumption]
readList :: ReadS [AssetPerfAssumption]
$creadPrec :: ReadPrec AssetPerfAssumption
readPrec :: ReadPrec AssetPerfAssumption
$creadListPrec :: ReadPrec [AssetPerfAssumption]
readListPrec :: ReadPrec [AssetPerfAssumption]
Read)
data RevolvingAssumption = AvailableAssets RevolvingPool ApplyAssumptionType
| AvailableAssetsBy (Map.Map String (RevolvingPool, ApplyAssumptionType))
deriving (Int -> RevolvingAssumption -> String -> String
[RevolvingAssumption] -> String -> String
RevolvingAssumption -> String
(Int -> RevolvingAssumption -> String -> String)
-> (RevolvingAssumption -> String)
-> ([RevolvingAssumption] -> String -> String)
-> Show RevolvingAssumption
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RevolvingAssumption -> String -> String
showsPrec :: Int -> RevolvingAssumption -> String -> String
$cshow :: RevolvingAssumption -> String
show :: RevolvingAssumption -> String
$cshowList :: [RevolvingAssumption] -> String -> String
showList :: [RevolvingAssumption] -> String -> String
Show,(forall x. RevolvingAssumption -> Rep RevolvingAssumption x)
-> (forall x. Rep RevolvingAssumption x -> RevolvingAssumption)
-> Generic RevolvingAssumption
forall x. Rep RevolvingAssumption x -> RevolvingAssumption
forall x. RevolvingAssumption -> Rep RevolvingAssumption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RevolvingAssumption -> Rep RevolvingAssumption x
from :: forall x. RevolvingAssumption -> Rep RevolvingAssumption x
$cto :: forall x. Rep RevolvingAssumption x -> RevolvingAssumption
to :: forall x. Rep RevolvingAssumption x -> RevolvingAssumption
Generic)
type HistoryCash = [(Date,Amount)]
type CurrentHolding = Balance
type PricingDate = Date
type AmountToBuy = Balance
data TradeType = ByCash Balance
| ByBalance Balance
deriving (Int -> TradeType -> String -> String
[TradeType] -> String -> String
TradeType -> String
(Int -> TradeType -> String -> String)
-> (TradeType -> String)
-> ([TradeType] -> String -> String)
-> Show TradeType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TradeType -> String -> String
showsPrec :: Int -> TradeType -> String -> String
$cshow :: TradeType -> String
show :: TradeType -> String
$cshowList :: [TradeType] -> String -> String
showList :: [TradeType] -> String -> String
Show,(forall x. TradeType -> Rep TradeType x)
-> (forall x. Rep TradeType x -> TradeType) -> Generic TradeType
forall x. Rep TradeType x -> TradeType
forall x. TradeType -> Rep TradeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TradeType -> Rep TradeType x
from :: forall x. TradeType -> Rep TradeType x
$cto :: forall x. Rep TradeType x -> TradeType
to :: forall x. Rep TradeType x -> TradeType
Generic)
data IrrType = HoldingBond HistoryCash CurrentHolding (Maybe (Date, BondPricingMethod))
| BuyBond Date BondPricingMethod TradeType (Maybe (Date, BondPricingMethod))
deriving (Int -> IrrType -> String -> String
[IrrType] -> String -> String
IrrType -> String
(Int -> IrrType -> String -> String)
-> (IrrType -> String)
-> ([IrrType] -> String -> String)
-> Show IrrType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> IrrType -> String -> String
showsPrec :: Int -> IrrType -> String -> String
$cshow :: IrrType -> String
show :: IrrType -> String
$cshowList :: [IrrType] -> String -> String
showList :: [IrrType] -> String -> String
Show,(forall x. IrrType -> Rep IrrType x)
-> (forall x. Rep IrrType x -> IrrType) -> Generic IrrType
forall x. Rep IrrType x -> IrrType
forall x. IrrType -> Rep IrrType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IrrType -> Rep IrrType x
from :: forall x. IrrType -> Rep IrrType x
$cto :: forall x. Rep IrrType x -> IrrType
to :: forall x. Rep IrrType x -> IrrType
Generic)
data BondPricingInput = DiscountCurve PricingDate Ts
| RunZSpread Ts (Map.Map BondName (Date,Rational))
| DiscountRate PricingDate Rate
| IrrInput (Map.Map BondName IrrType)
deriving (Int -> BondPricingInput -> String -> String
[BondPricingInput] -> String -> String
BondPricingInput -> String
(Int -> BondPricingInput -> String -> String)
-> (BondPricingInput -> String)
-> ([BondPricingInput] -> String -> String)
-> Show BondPricingInput
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> BondPricingInput -> String -> String
showsPrec :: Int -> BondPricingInput -> String -> String
$cshow :: BondPricingInput -> String
show :: BondPricingInput -> String
$cshowList :: [BondPricingInput] -> String -> String
showList :: [BondPricingInput] -> String -> String
Show,(forall x. BondPricingInput -> Rep BondPricingInput x)
-> (forall x. Rep BondPricingInput x -> BondPricingInput)
-> Generic BondPricingInput
forall x. Rep BondPricingInput x -> BondPricingInput
forall x. BondPricingInput -> Rep BondPricingInput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BondPricingInput -> Rep BondPricingInput x
from :: forall x. BondPricingInput -> Rep BondPricingInput x
$cto :: forall x. Rep BondPricingInput x -> BondPricingInput
to :: forall x. Rep BondPricingInput x -> BondPricingInput
Generic)
getIndexFromRateAssumption :: RateAssumption -> Index
getIndexFromRateAssumption :: RateAssumption -> Index
getIndexFromRateAssumption (RateCurve Index
idx Ts
_) = Index
idx
getIndexFromRateAssumption (RateFlat Index
idx IRate
_) = Index
idx
lookupRate :: [RateAssumption] -> Floater -> Date -> Either String IRate
lookupRate :: [RateAssumption] -> Floater -> Date -> Either String IRate
lookupRate [RateAssumption]
rAssumps (Index
index,IRate
spd) Date
d
= case (RateAssumption -> Bool)
-> [RateAssumption] -> Maybe RateAssumption
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\RateAssumption
x -> RateAssumption -> Index
getIndexFromRateAssumption RateAssumption
x Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
== Index
index ) [RateAssumption]
rAssumps of
Just (RateCurve Index
_ Ts
ts) -> IRate -> Either String IRate
forall a b. b -> Either a b
Right (IRate -> Either String IRate) -> IRate -> Either String IRate
forall a b. (a -> b) -> a -> b
$ IRate
spd IRate -> IRate -> IRate
forall a. Num a => a -> a -> a
+ Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational (Ts -> CutoffType -> Date -> Rate
getValByDate Ts
ts CutoffType
Inc Date
d)
Just (RateFlat Index
_ IRate
r) -> IRate -> Either String IRate
forall a b. b -> Either a b
Right (IRate -> Either String IRate) -> IRate -> Either String IRate
forall a b. (a -> b) -> a -> b
$ IRate
r IRate -> IRate -> IRate
forall a. Num a => a -> a -> a
+ IRate
spd
Maybe RateAssumption
Nothing -> String -> Either String IRate
forall a b. a -> Either a b
Left (String -> Either String IRate) -> String -> Either String IRate
forall a b. (a -> b) -> a -> b
$ String
"Failed to find Index " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Index -> String
forall a. Show a => a -> String
show Index
index String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"in list "String -> String -> String
forall a. [a] -> [a] -> [a]
++ [RateAssumption] -> String
forall a. Show a => a -> String
show [RateAssumption]
rAssumps
lookupRate0 :: [RateAssumption] -> Index -> Date -> Either String IRate
lookupRate0 :: [RateAssumption] -> Index -> Date -> Either String IRate
lookupRate0 [RateAssumption]
rAssumps Index
index Date
d
= case (RateAssumption -> Bool)
-> [RateAssumption] -> Maybe RateAssumption
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\RateAssumption
x -> RateAssumption -> Index
getIndexFromRateAssumption RateAssumption
x Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
== Index
index ) [RateAssumption]
rAssumps of
Just (RateCurve Index
_ Ts
ts) -> IRate -> Either String IRate
forall a b. b -> Either a b
Right (IRate -> Either String IRate) -> IRate -> Either String IRate
forall a b. (a -> b) -> a -> b
$ Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational (Ts -> CutoffType -> Date -> Rate
getValByDate Ts
ts CutoffType
Inc Date
d)
Just (RateFlat Index
_ IRate
r) -> IRate -> Either String IRate
forall a b. b -> Either a b
Right IRate
r
Maybe RateAssumption
Nothing -> String -> Either String IRate
forall a b. a -> Either a b
Left (String -> Either String IRate) -> String -> Either String IRate
forall a b. (a -> b) -> a -> b
$ String
"Failed to find Index " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Index -> String
forall a. Show a => a -> String
show Index
index String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" from Rate Assumption" String -> String -> String
forall a. [a] -> [a] -> [a]
++ [RateAssumption] -> String
forall a. Show a => a -> String
show [RateAssumption]
rAssumps
getRateAssumption :: [RateAssumption] -> Index -> Maybe RateAssumption
getRateAssumption :: [RateAssumption] -> Index -> Maybe RateAssumption
getRateAssumption [RateAssumption]
assumps Index
idx
= (RateAssumption -> Bool)
-> [RateAssumption] -> Maybe RateAssumption
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\case
(RateCurve Index
_idx Ts
_) -> Index
idx Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
== Index
_idx
(RateFlat Index
_idx IRate
_) -> Index
idx Index -> Index -> Bool
forall a. Eq a => a -> a -> Bool
== Index
_idx
RateAssumption
_ -> Bool
False)
[RateAssumption]
assumps
projRates :: IRate -> RateType -> Maybe [RateAssumption] -> [Date] -> Either String [IRate]
projRates :: IRate
-> RateType
-> Maybe [RateAssumption]
-> [Date]
-> Either String [IRate]
projRates IRate
sr RateType
_ Maybe [RateAssumption]
_ [] = String -> Either String [IRate]
forall a b. a -> Either a b
Left String
"No dates provided for rate projection"
projRates IRate
sr (Fix DayCount
_ IRate
r) Maybe [RateAssumption]
_ [Date]
ds = [IRate] -> Either String [IRate]
forall a b. b -> Either a b
Right ([IRate] -> Either String [IRate])
-> [IRate] -> Either String [IRate]
forall a b. (a -> b) -> a -> b
$ Int -> IRate -> [IRate]
forall a. Int -> a -> [a]
replicate ([Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
ds) IRate
sr
projRates IRate
sr (Floater DayCount
_ Index
idx IRate
spd IRate
r DatePattern
dp RateFloor
rfloor RateFloor
rcap Maybe (RoundingBy IRate)
mr) Maybe [RateAssumption]
Nothing [Date]
ds = String -> Either String [IRate]
forall a b. a -> Either a b
Left (String -> Either String [IRate])
-> String -> Either String [IRate]
forall a b. (a -> b) -> a -> b
$ String
"Looking up rate error: No rate assumption found for index "String -> String -> String
forall a. [a] -> [a] -> [a]
++ Index -> String
forall a. Show a => a -> String
show Index
idx
projRates IRate
sr (Floater DayCount
_ Index
idx IRate
spd IRate
r DatePattern
dp RateFloor
rfloor RateFloor
rcap Maybe (RoundingBy IRate)
mr) (Just [RateAssumption]
assumps) [Date]
ds
= case [RateAssumption] -> Index -> Maybe RateAssumption
getRateAssumption [RateAssumption]
assumps Index
idx of
Maybe RateAssumption
Nothing -> String -> Either String [IRate]
forall a b. a -> Either a b
Left (String
"Failed to find index rate " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Index -> String
forall a. Show a => a -> String
show Index
idx String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" from "String -> String -> String
forall a. [a] -> [a] -> [a]
++ [RateAssumption] -> String
forall a. Show a => a -> String
show [RateAssumption]
assumps)
Just RateAssumption
_rateAssumption ->
[IRate] -> Either String [IRate]
forall a b. b -> Either a b
Right ([IRate] -> Either String [IRate])
-> [IRate] -> Either String [IRate]
forall a b. (a -> b) -> a -> b
$
let
resetDates :: [Date]
resetDates = RangeType -> Date -> DatePattern -> Date -> [Date]
genSerialDatesTill2 RangeType
NO_IE ([Date] -> Date
forall a. HasCallStack => [a] -> a
head [Date]
ds) DatePattern
dp ([Date] -> Date
forall a. HasCallStack => [a] -> a
last [Date]
ds)
ratesFromCurve :: [IRate]
ratesFromCurve = case RateAssumption
_rateAssumption of
(RateCurve Index
_ Ts
ts) -> (\Rate
x -> IRate
spd IRate -> IRate -> IRate
forall a. Num a => a -> a -> a
+ (Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational Rate
x) ) (Rate -> IRate) -> [Rate] -> [IRate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ts -> CutoffType -> [Date] -> [Rate]
getValByDates Ts
ts CutoffType
Inc [Date]
resetDates)
(RateFlat Index
_ IRate
v) -> (IRate
spd IRate -> IRate -> IRate
forall a. Num a => a -> a -> a
+) (IRate -> IRate) -> [IRate] -> [IRate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> IRate -> [IRate]
forall a. Int -> a -> [a]
replicate ([Date] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Date]
resetDates) IRate
v
ratesUsedByDates :: [Rate]
ratesUsedByDates = Ts -> CutoffType -> [Date] -> [Rate]
getValByDates
([(Date, IRate)] -> Ts
mkRateTs ([(Date, IRate)] -> Ts) -> [(Date, IRate)] -> Ts
forall a b. (a -> b) -> a -> b
$ [Date] -> [IRate] -> [(Date, IRate)]
forall a b. [a] -> [b] -> [(a, b)]
zip (([Date] -> Date
forall a. HasCallStack => [a] -> a
head [Date]
ds)Date -> [Date] -> [Date]
forall a. a -> [a] -> [a]
:[Date]
resetDates) (IRate
srIRate -> [IRate] -> [IRate]
forall a. a -> [a] -> [a]
:[IRate]
ratesFromCurve))
CutoffType
Inc
[Date]
ds
in
case (RateFloor
rfloor,RateFloor
rcap) of
(RateFloor
Nothing, RateFloor
Nothing) -> Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational (Rate -> IRate) -> [Rate] -> [IRate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
ratesUsedByDates
(Just IRate
fv, Just IRate
cv) -> IRate -> [IRate] -> [IRate]
forall a. Ord a => a -> [a] -> [a]
capWith IRate
cv ([IRate] -> [IRate]) -> [IRate] -> [IRate]
forall a b. (a -> b) -> a -> b
$ IRate -> [IRate] -> [IRate]
forall a. Ord a => a -> [a] -> [a]
floorWith IRate
fv ([IRate] -> [IRate]) -> [IRate] -> [IRate]
forall a b. (a -> b) -> a -> b
$ Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational (Rate -> IRate) -> [Rate] -> [IRate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
ratesUsedByDates
(Just IRate
fv, RateFloor
Nothing) -> IRate -> [IRate] -> [IRate]
forall a. Ord a => a -> [a] -> [a]
floorWith IRate
fv ([IRate] -> [IRate]) -> [IRate] -> [IRate]
forall a b. (a -> b) -> a -> b
$ Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational (Rate -> IRate) -> [Rate] -> [IRate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
ratesUsedByDates
(RateFloor
Nothing, Just IRate
cv) -> IRate -> [IRate] -> [IRate]
forall a. Ord a => a -> [a] -> [a]
capWith IRate
cv ([IRate] -> [IRate]) -> [IRate] -> [IRate]
forall a b. (a -> b) -> a -> b
$ Rate -> IRate
forall a. Fractional a => Rate -> a
fromRational (Rate -> IRate) -> [Rate] -> [IRate]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rate]
ratesUsedByDates
projRates IRate
_ RateType
rt Maybe [RateAssumption]
rassump [Date]
ds = String -> Either String [IRate]
forall a b. a -> Either a b
Left (String
"Invalid rate type: "String -> String -> String
forall a. [a] -> [a] -> [a]
++ RateType -> String
forall a. Show a => a -> String
show RateType
rtString -> String -> String
forall a. [a] -> [a] -> [a]
++String
" assump: "String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe [RateAssumption] -> String
forall a. Show a => a -> String
show Maybe [RateAssumption]
rassump)
makePrisms ''AssetPerfAssumption
makePrisms ''AssetDefaultAssumption
$(deriveJSON defaultOptions ''CallOpt)
$(deriveJSON defaultOptions ''TradeType)
$(deriveJSON defaultOptions ''IrrType)
$(deriveJSON defaultOptions ''BondPricingInput)
$(deriveJSON defaultOptions ''IssueBondEvent)
$(deriveJSON defaultOptions ''RefiEvent)
$(concat <$> traverse (deriveJSON defaultOptions) [''LeaseDefaultType, ''LeaseEndType,''FieldMatchRule,''TagMatchRule, ''ObligorStrategy,''ApplyAssumptionType, ''AssetPerfAssumption, ''StopBy
, ''AssetDefaultedPerfAssumption, ''AssetDelinqPerfAssumption, ''NonPerfAssumption, ''AssetDefaultAssumption
, ''AssetPrepayAssumption, ''RecoveryAssumption, ''ExtraStress
, ''LeaseAssetGapAssump, ''LeaseAssetRentAssump, ''RevolvingAssumption, ''AssetDelinquencyAssumption,''InspectType])