{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE InstanceSigs #-}
module Liability
(Bond(..),BondType(..),OriginalInfo(..)
,payInt,payPrin,consolStmt,isPaidOff,getCurBalance
,priceBond,pv,InterestInfo(..),RateReset(..)
,getDueInt,weightAverageBalance,calcZspread,payYield,getTotalDueInt
,buildRateResetDates,isAdjustble,StepUp(..),isStepUp,getDayCountFromInfo
,calcWalBond,patchBondFactor,fundWith,writeOff,InterestOverInterestType(..)
,getCurBalance,setBondOrigDate
,bndOriginInfoLens,bndIntLens,getBeginRate,_Bond,_BondGroup
,totalFundedBalance,getIndexFromInfo,buildStepUpDates
,accrueInt,stepUpInterestInfo,payIntByIndex,_MultiIntBond
,getDueIntAt,getDueIntOverIntAt,getDueIntOverInt,getTotalDueIntAt
,getCurRate,bondCashflow,getOutstandingAmount,valueBond,getTxnRate
,getAccrueBegDate,getTxnInt,adjInterestInfoByRate,adjInterestInfoBySpread
,interestInfoTraversal,getOriginBalance,curRatesTraversal
,backoutAccruedInt,extractIrrResult,adjustBalance
)
where
import Data.Aeson hiding (json)
import Data.Aeson.TH
import Data.Fixed
import qualified Data.Time as T
import Lib (Period(..),Ts(..) ,TsPoint(..) ,daysBetween, weightedBy,paySeqLiabResi)
import Util
import DateUtil
import Types
import Analytics
import Data.Ratio
import Data.Maybe
import Data.List
import qualified Data.Set as Set
import qualified Data.DList as DL
import qualified Stmt as S
import qualified Cashflow as CF
import qualified InterestRate as IR
import qualified Lib
import GHC.Generics
import qualified Data.Map as Map
import Debug.Trace
import InterestRate (UseRate(getIndexes))
import Language.Haskell.TH
import Control.Lens hiding (Index)
import Control.Lens.TH
import Language.Haskell.TH.Lens
import Stmt (getTxnAmt)
import Numeric.RootFinding
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
isAdjustble :: InterestInfo -> Bool
isAdjustble :: InterestInfo -> Bool
isAdjustble Floater {} = Bool
True
isAdjustble RefRate {} = Bool
True
isAdjustble Fix {} = Bool
False
isAdjustble (CapRate InterestInfo
r Spread
_ ) = InterestInfo -> Bool
isAdjustble InterestInfo
r
isAdjustble (FloorRate InterestInfo
r Spread
_ ) = InterestInfo -> Bool
isAdjustble InterestInfo
r
isAdjustble (WithIoI InterestInfo
r InterestOverInterestType
_) = InterestInfo -> Bool
isAdjustble InterestInfo
r
isAdjustble (RefBal DealStats
_ InterestInfo
r) = InterestInfo -> Bool
isAdjustble InterestInfo
r
isStepUp :: Bond -> Bool
isStepUp :: Bond -> Bool
isStepUp Bond{bndStepUp :: Bond -> Maybe StepUp
bndStepUp = Maybe StepUp
Nothing} = Bool
False
isStepUp Bond
_ = Bool
True
getIndexFromInfo :: InterestInfo -> Maybe [Index]
getIndexFromInfo :: InterestInfo -> Maybe [Index]
getIndexFromInfo (Floater Spread
_ Index
idx Spread
_ RateReset
_ DayCount
_ Maybe Spread
_ Maybe Spread
_) = [Index] -> Maybe [Index]
forall a. a -> Maybe a
Just [Index
idx]
getIndexFromInfo Fix {} = Maybe [Index]
forall a. Maybe a
Nothing
getIndexFromInfo RefRate {} = Maybe [Index]
forall a. Maybe a
Nothing
getIndexFromInfo (CapRate InterestInfo
info Spread
_) = InterestInfo -> Maybe [Index]
getIndexFromInfo InterestInfo
info
getIndexFromInfo (FloorRate InterestInfo
info Spread
_) = InterestInfo -> Maybe [Index]
getIndexFromInfo InterestInfo
info
getIndexFromInfo (WithIoI InterestInfo
info InterestOverInterestType
_) = InterestInfo -> Maybe [Index]
getIndexFromInfo InterestInfo
info
getIndexFromInfo (RefBal DealStats
_ InterestInfo
info) = InterestInfo -> Maybe [Index]
getIndexFromInfo InterestInfo
info
getDayCountFromInfo :: InterestInfo -> Maybe DayCount
getDayCountFromInfo :: InterestInfo -> Maybe DayCount
getDayCountFromInfo (Floater Spread
_ Index
_ Spread
_ RateReset
_ DayCount
dc Maybe Spread
_ Maybe Spread
_) = DayCount -> Maybe DayCount
forall a. a -> Maybe a
Just DayCount
dc
getDayCountFromInfo (Fix Spread
_ DayCount
dc) = DayCount -> Maybe DayCount
forall a. a -> Maybe a
Just DayCount
dc
getDayCountFromInfo RefRate {} = Maybe DayCount
forall a. Maybe a
Nothing
getDayCountFromInfo (RefBal DealStats
ds InterestInfo
info) = InterestInfo -> Maybe DayCount
getDayCountFromInfo InterestInfo
info
getDayCountFromInfo (CapRate InterestInfo
info Spread
_) = InterestInfo -> Maybe DayCount
getDayCountFromInfo InterestInfo
info
getDayCountFromInfo (FloorRate InterestInfo
info Spread
_) = InterestInfo -> Maybe DayCount
getDayCountFromInfo InterestInfo
info
getDayCountFromInfo (WithIoI InterestInfo
info InterestOverInterestType
_) = InterestInfo -> Maybe DayCount
getDayCountFromInfo InterestInfo
info
getDayCountFromInfo InterestInfo
_ = Maybe DayCount
forall a. Maybe a
Nothing
type RateReset = DatePattern
data InterestOverInterestType = OverCurrRateBy Rational
| OverFixSpread Spread
deriving (Int -> InterestOverInterestType -> ShowS
[InterestOverInterestType] -> ShowS
InterestOverInterestType -> String
(Int -> InterestOverInterestType -> ShowS)
-> (InterestOverInterestType -> String)
-> ([InterestOverInterestType] -> ShowS)
-> Show InterestOverInterestType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InterestOverInterestType -> ShowS
showsPrec :: Int -> InterestOverInterestType -> ShowS
$cshow :: InterestOverInterestType -> String
show :: InterestOverInterestType -> String
$cshowList :: [InterestOverInterestType] -> ShowS
showList :: [InterestOverInterestType] -> ShowS
Show, InterestOverInterestType -> InterestOverInterestType -> Bool
(InterestOverInterestType -> InterestOverInterestType -> Bool)
-> (InterestOverInterestType -> InterestOverInterestType -> Bool)
-> Eq InterestOverInterestType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterestOverInterestType -> InterestOverInterestType -> Bool
== :: InterestOverInterestType -> InterestOverInterestType -> Bool
$c/= :: InterestOverInterestType -> InterestOverInterestType -> Bool
/= :: InterestOverInterestType -> InterestOverInterestType -> Bool
Eq, (forall x.
InterestOverInterestType -> Rep InterestOverInterestType x)
-> (forall x.
Rep InterestOverInterestType x -> InterestOverInterestType)
-> Generic InterestOverInterestType
forall x.
Rep InterestOverInterestType x -> InterestOverInterestType
forall x.
InterestOverInterestType -> Rep InterestOverInterestType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
InterestOverInterestType -> Rep InterestOverInterestType x
from :: forall x.
InterestOverInterestType -> Rep InterestOverInterestType x
$cto :: forall x.
Rep InterestOverInterestType x -> InterestOverInterestType
to :: forall x.
Rep InterestOverInterestType x -> InterestOverInterestType
Generic, Eq InterestOverInterestType
Eq InterestOverInterestType =>
(InterestOverInterestType -> InterestOverInterestType -> Ordering)
-> (InterestOverInterestType -> InterestOverInterestType -> Bool)
-> (InterestOverInterestType -> InterestOverInterestType -> Bool)
-> (InterestOverInterestType -> InterestOverInterestType -> Bool)
-> (InterestOverInterestType -> InterestOverInterestType -> Bool)
-> (InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType)
-> (InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType)
-> Ord InterestOverInterestType
InterestOverInterestType -> InterestOverInterestType -> Bool
InterestOverInterestType -> InterestOverInterestType -> Ordering
InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType
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 :: InterestOverInterestType -> InterestOverInterestType -> Ordering
compare :: InterestOverInterestType -> InterestOverInterestType -> Ordering
$c< :: InterestOverInterestType -> InterestOverInterestType -> Bool
< :: InterestOverInterestType -> InterestOverInterestType -> Bool
$c<= :: InterestOverInterestType -> InterestOverInterestType -> Bool
<= :: InterestOverInterestType -> InterestOverInterestType -> Bool
$c> :: InterestOverInterestType -> InterestOverInterestType -> Bool
> :: InterestOverInterestType -> InterestOverInterestType -> Bool
$c>= :: InterestOverInterestType -> InterestOverInterestType -> Bool
>= :: InterestOverInterestType -> InterestOverInterestType -> Bool
$cmax :: InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType
max :: InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType
$cmin :: InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType
min :: InterestOverInterestType
-> InterestOverInterestType -> InterestOverInterestType
Ord, ReadPrec [InterestOverInterestType]
ReadPrec InterestOverInterestType
Int -> ReadS InterestOverInterestType
ReadS [InterestOverInterestType]
(Int -> ReadS InterestOverInterestType)
-> ReadS [InterestOverInterestType]
-> ReadPrec InterestOverInterestType
-> ReadPrec [InterestOverInterestType]
-> Read InterestOverInterestType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterestOverInterestType
readsPrec :: Int -> ReadS InterestOverInterestType
$creadList :: ReadS [InterestOverInterestType]
readList :: ReadS [InterestOverInterestType]
$creadPrec :: ReadPrec InterestOverInterestType
readPrec :: ReadPrec InterestOverInterestType
$creadListPrec :: ReadPrec [InterestOverInterestType]
readListPrec :: ReadPrec [InterestOverInterestType]
Read)
data InterestInfo = Floater IRate Index Spread RateReset DayCount (Maybe Floor) (Maybe Cap)
| Fix IRate DayCount
| RefBal DealStats InterestInfo
| RefRate IRate DealStats Float RateReset
| CapRate InterestInfo IRate
| FloorRate InterestInfo IRate
| WithIoI InterestInfo InterestOverInterestType
deriving (Int -> InterestInfo -> ShowS
[InterestInfo] -> ShowS
InterestInfo -> String
(Int -> InterestInfo -> ShowS)
-> (InterestInfo -> String)
-> ([InterestInfo] -> ShowS)
-> Show InterestInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InterestInfo -> ShowS
showsPrec :: Int -> InterestInfo -> ShowS
$cshow :: InterestInfo -> String
show :: InterestInfo -> String
$cshowList :: [InterestInfo] -> ShowS
showList :: [InterestInfo] -> ShowS
Show, InterestInfo -> InterestInfo -> Bool
(InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool) -> Eq InterestInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterestInfo -> InterestInfo -> Bool
== :: InterestInfo -> InterestInfo -> Bool
$c/= :: InterestInfo -> InterestInfo -> Bool
/= :: InterestInfo -> InterestInfo -> Bool
Eq, (forall x. InterestInfo -> Rep InterestInfo x)
-> (forall x. Rep InterestInfo x -> InterestInfo)
-> Generic InterestInfo
forall x. Rep InterestInfo x -> InterestInfo
forall x. InterestInfo -> Rep InterestInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InterestInfo -> Rep InterestInfo x
from :: forall x. InterestInfo -> Rep InterestInfo x
$cto :: forall x. Rep InterestInfo x -> InterestInfo
to :: forall x. Rep InterestInfo x -> InterestInfo
Generic, Eq InterestInfo
Eq InterestInfo =>
(InterestInfo -> InterestInfo -> Ordering)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> InterestInfo)
-> (InterestInfo -> InterestInfo -> InterestInfo)
-> Ord InterestInfo
InterestInfo -> InterestInfo -> Bool
InterestInfo -> InterestInfo -> Ordering
InterestInfo -> InterestInfo -> InterestInfo
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 :: InterestInfo -> InterestInfo -> Ordering
compare :: InterestInfo -> InterestInfo -> Ordering
$c< :: InterestInfo -> InterestInfo -> Bool
< :: InterestInfo -> InterestInfo -> Bool
$c<= :: InterestInfo -> InterestInfo -> Bool
<= :: InterestInfo -> InterestInfo -> Bool
$c> :: InterestInfo -> InterestInfo -> Bool
> :: InterestInfo -> InterestInfo -> Bool
$c>= :: InterestInfo -> InterestInfo -> Bool
>= :: InterestInfo -> InterestInfo -> Bool
$cmax :: InterestInfo -> InterestInfo -> InterestInfo
max :: InterestInfo -> InterestInfo -> InterestInfo
$cmin :: InterestInfo -> InterestInfo -> InterestInfo
min :: InterestInfo -> InterestInfo -> InterestInfo
Ord, ReadPrec [InterestInfo]
ReadPrec InterestInfo
Int -> ReadS InterestInfo
ReadS [InterestInfo]
(Int -> ReadS InterestInfo)
-> ReadS [InterestInfo]
-> ReadPrec InterestInfo
-> ReadPrec [InterestInfo]
-> Read InterestInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterestInfo
readsPrec :: Int -> ReadS InterestInfo
$creadList :: ReadS [InterestInfo]
readList :: ReadS [InterestInfo]
$creadPrec :: ReadPrec InterestInfo
readPrec :: ReadPrec InterestInfo
$creadListPrec :: ReadPrec [InterestInfo]
readListPrec :: ReadPrec [InterestInfo]
Read)
adjInterestInfoByRate :: Rate -> InterestInfo -> InterestInfo
adjInterestInfoByRate :: Rational -> InterestInfo -> InterestInfo
adjInterestInfoByRate Rational
r (Floater Spread
a Index
idx Spread
s RateReset
dp DayCount
dc Maybe Spread
f Maybe Spread
c) = Spread
-> Index
-> Spread
-> RateReset
-> DayCount
-> Maybe Spread
-> Maybe Spread
-> InterestInfo
Floater (Spread
aSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
* Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational Rational
r) Index
idx (Spread
sSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
* Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational Rational
r) RateReset
dp DayCount
dc Maybe Spread
f Maybe Spread
c
adjInterestInfoByRate Rational
r (Fix Spread
a DayCount
dc) = Spread -> DayCount -> InterestInfo
Fix (Spread
aSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
* Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational Rational
r) DayCount
dc
adjInterestInfoByRate Rational
r (RefRate Spread
a DealStats
ds Float
f RateReset
dp) = Spread -> DealStats -> Float -> RateReset -> InterestInfo
RefRate (Spread
aSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
* Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational Rational
r) DealStats
ds (Float
fFloat -> Float -> Float
forall a. Num a => a -> a -> a
* Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
r) RateReset
dp
adjInterestInfoByRate Rational
r (RefBal DealStats
ds InterestInfo
ii) = DealStats -> InterestInfo -> InterestInfo
RefBal DealStats
ds (Rational -> InterestInfo -> InterestInfo
adjInterestInfoByRate Rational
r InterestInfo
ii)
adjInterestInfoByRate Rational
r (CapRate InterestInfo
ii Spread
a) = InterestInfo -> Spread -> InterestInfo
CapRate (Rational -> InterestInfo -> InterestInfo
adjInterestInfoByRate Rational
r InterestInfo
ii) Spread
a
adjInterestInfoByRate Rational
r (FloorRate InterestInfo
ii Spread
a) = InterestInfo -> Spread -> InterestInfo
FloorRate (Rational -> InterestInfo -> InterestInfo
adjInterestInfoByRate Rational
r InterestInfo
ii) Spread
a
adjInterestInfoByRate Rational
r (WithIoI InterestInfo
ii InterestOverInterestType
ooi) = InterestInfo -> InterestOverInterestType -> InterestInfo
WithIoI (Rational -> InterestInfo -> InterestInfo
adjInterestInfoByRate Rational
r InterestInfo
ii) InterestOverInterestType
ooi
adjInterestInfoBySpread :: Spread -> InterestInfo -> InterestInfo
adjInterestInfoBySpread :: Spread -> InterestInfo -> InterestInfo
adjInterestInfoBySpread Spread
s (Floater Spread
a Index
idx Spread
s' RateReset
dp DayCount
dc Maybe Spread
f Maybe Spread
c) = Spread
-> Index
-> Spread
-> RateReset
-> DayCount
-> Maybe Spread
-> Maybe Spread
-> InterestInfo
Floater Spread
s Index
idx (Spread
sSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
+Spread
s') RateReset
dp DayCount
dc Maybe Spread
f Maybe Spread
c
adjInterestInfoBySpread Spread
s (Fix Spread
a DayCount
dc) = Spread -> DayCount -> InterestInfo
Fix (Spread
aSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
+Spread
s) DayCount
dc
adjInterestInfoBySpread Spread
s (RefRate Spread
a DealStats
ds Float
f RateReset
dp) = Spread -> DealStats -> Float -> RateReset -> InterestInfo
RefRate (Spread
aSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
+Spread
s) DealStats
ds Float
f RateReset
dp
adjInterestInfoBySpread Spread
s (RefBal DealStats
ds InterestInfo
ii) = DealStats -> InterestInfo -> InterestInfo
RefBal DealStats
ds (Spread -> InterestInfo -> InterestInfo
adjInterestInfoBySpread Spread
s InterestInfo
ii)
adjInterestInfoBySpread Spread
s (CapRate InterestInfo
ii Spread
a) = InterestInfo -> Spread -> InterestInfo
CapRate (Spread -> InterestInfo -> InterestInfo
adjInterestInfoBySpread Spread
s InterestInfo
ii) Spread
a
adjInterestInfoBySpread Spread
s (FloorRate InterestInfo
ii Spread
a) = InterestInfo -> Spread -> InterestInfo
FloorRate (Spread -> InterestInfo -> InterestInfo
adjInterestInfoBySpread Spread
s InterestInfo
ii) Spread
a
adjInterestInfoBySpread Spread
s (WithIoI InterestInfo
ii InterestOverInterestType
ooi) = InterestInfo -> InterestOverInterestType -> InterestInfo
WithIoI (Spread -> InterestInfo -> InterestInfo
adjInterestInfoBySpread Spread
s InterestInfo
ii) InterestOverInterestType
ooi
stepUpInterestInfo :: StepUp -> InterestInfo -> InterestInfo
stepUpInterestInfo :: StepUp -> InterestInfo -> InterestInfo
stepUpInterestInfo StepUp
sp InterestInfo
ii =
case InterestInfo
ii of
(Floater Spread
a Index
idx Spread
s RateReset
dp DayCount
dc Maybe Spread
f Maybe Spread
c) -> Spread
-> Index
-> Spread
-> RateReset
-> DayCount
-> Maybe Spread
-> Maybe Spread
-> InterestInfo
Floater Spread
a Index
idx (Spread
sSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
+StepUp -> Spread
getSpread StepUp
sp) RateReset
dp DayCount
dc Maybe Spread
f Maybe Spread
c
(Fix Spread
r DayCount
dc) -> Spread -> DayCount -> InterestInfo
Fix (Spread
rSpread -> Spread -> Spread
forall a. Num a => a -> a -> a
+StepUp -> Spread
getSpread StepUp
sp) DayCount
dc
(CapRate InterestInfo
ii' Spread
r) -> InterestInfo -> Spread -> InterestInfo
CapRate (StepUp -> InterestInfo -> InterestInfo
stepUpInterestInfo StepUp
sp InterestInfo
ii') Spread
r
(FloorRate InterestInfo
ii' Spread
r) -> InterestInfo -> Spread -> InterestInfo
FloorRate (StepUp -> InterestInfo -> InterestInfo
stepUpInterestInfo StepUp
sp InterestInfo
ii') Spread
r
(WithIoI InterestInfo
ii' InterestOverInterestType
ooi) -> InterestInfo -> InterestOverInterestType -> InterestInfo
WithIoI (StepUp -> InterestInfo -> InterestInfo
stepUpInterestInfo StepUp
sp InterestInfo
ii') InterestOverInterestType
ooi
(RefBal DealStats
ds InterestInfo
ii') -> DealStats -> InterestInfo -> InterestInfo
RefBal DealStats
ds (StepUp -> InterestInfo -> InterestInfo
stepUpInterestInfo StepUp
sp InterestInfo
ii')
InterestInfo
_ -> InterestInfo
ii
where
getSpread :: StepUp -> Spread
getSpread (PassDateSpread Date
_ Spread
s) = Spread
s
getSpread (PassDateLadderSpread Date
_ Spread
s RateReset
_) = Spread
s
getDpFromIntInfo :: InterestInfo -> Maybe DatePattern
getDpFromIntInfo :: InterestInfo -> Maybe RateReset
getDpFromIntInfo (Floater Spread
_ Index
_ Spread
_ RateReset
dp DayCount
_ Maybe Spread
_ Maybe Spread
_) = RateReset -> Maybe RateReset
forall a. a -> Maybe a
Just RateReset
dp
getDpFromIntInfo (RefRate Spread
_ DealStats
_ Float
_ RateReset
dp) = RateReset -> Maybe RateReset
forall a. a -> Maybe a
Just RateReset
dp
getDpFromIntInfo (RefBal DealStats
_ InterestInfo
ii) = InterestInfo -> Maybe RateReset
getDpFromIntInfo InterestInfo
ii
getDpFromIntInfo (CapRate InterestInfo
ii Spread
_) = InterestInfo -> Maybe RateReset
getDpFromIntInfo InterestInfo
ii
getDpFromIntInfo (FloorRate InterestInfo
ii Spread
_) = InterestInfo -> Maybe RateReset
getDpFromIntInfo InterestInfo
ii
getDpFromIntInfo (WithIoI InterestInfo
ii InterestOverInterestType
_) = InterestInfo -> Maybe RateReset
getDpFromIntInfo InterestInfo
ii
getDpFromIntInfo InterestInfo
_ = Maybe RateReset
forall a. Maybe a
Nothing
getBeginRate :: InterestInfo -> IRate
getBeginRate :: InterestInfo -> Spread
getBeginRate (Floater Spread
a Index
_ Spread
_ RateReset
_ DayCount
_ Maybe Spread
_ Maybe Spread
_ ) = Spread
a
getBeginRate (Fix Spread
a DayCount
_ ) = Spread
a
getBeginRate (RefRate Spread
a DealStats
_ Float
_ RateReset
_ ) = Spread
a
getBeginRate (CapRate InterestInfo
a Spread
_ ) = InterestInfo -> Spread
getBeginRate InterestInfo
a
getBeginRate (FloorRate InterestInfo
a Spread
_ ) = InterestInfo -> Spread
getBeginRate InterestInfo
a
getBeginRate (WithIoI InterestInfo
a InterestOverInterestType
_) = InterestInfo -> Spread
getBeginRate InterestInfo
a
getBeginRate (RefBal DealStats
_ InterestInfo
a) = InterestInfo -> Spread
getBeginRate InterestInfo
a
data StepUp = PassDateSpread Date Spread
| PassDateLadderSpread Date Spread RateReset
deriving (Int -> StepUp -> ShowS
[StepUp] -> ShowS
StepUp -> String
(Int -> StepUp -> ShowS)
-> (StepUp -> String) -> ([StepUp] -> ShowS) -> Show StepUp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StepUp -> ShowS
showsPrec :: Int -> StepUp -> ShowS
$cshow :: StepUp -> String
show :: StepUp -> String
$cshowList :: [StepUp] -> ShowS
showList :: [StepUp] -> ShowS
Show, StepUp -> StepUp -> Bool
(StepUp -> StepUp -> Bool)
-> (StepUp -> StepUp -> Bool) -> Eq StepUp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StepUp -> StepUp -> Bool
== :: StepUp -> StepUp -> Bool
$c/= :: StepUp -> StepUp -> Bool
/= :: StepUp -> StepUp -> Bool
Eq, (forall x. StepUp -> Rep StepUp x)
-> (forall x. Rep StepUp x -> StepUp) -> Generic StepUp
forall x. Rep StepUp x -> StepUp
forall x. StepUp -> Rep StepUp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StepUp -> Rep StepUp x
from :: forall x. StepUp -> Rep StepUp x
$cto :: forall x. Rep StepUp x -> StepUp
to :: forall x. Rep StepUp x -> StepUp
Generic, Eq StepUp
Eq StepUp =>
(StepUp -> StepUp -> Ordering)
-> (StepUp -> StepUp -> Bool)
-> (StepUp -> StepUp -> Bool)
-> (StepUp -> StepUp -> Bool)
-> (StepUp -> StepUp -> Bool)
-> (StepUp -> StepUp -> StepUp)
-> (StepUp -> StepUp -> StepUp)
-> Ord StepUp
StepUp -> StepUp -> Bool
StepUp -> StepUp -> Ordering
StepUp -> StepUp -> StepUp
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 :: StepUp -> StepUp -> Ordering
compare :: StepUp -> StepUp -> Ordering
$c< :: StepUp -> StepUp -> Bool
< :: StepUp -> StepUp -> Bool
$c<= :: StepUp -> StepUp -> Bool
<= :: StepUp -> StepUp -> Bool
$c> :: StepUp -> StepUp -> Bool
> :: StepUp -> StepUp -> Bool
$c>= :: StepUp -> StepUp -> Bool
>= :: StepUp -> StepUp -> Bool
$cmax :: StepUp -> StepUp -> StepUp
max :: StepUp -> StepUp -> StepUp
$cmin :: StepUp -> StepUp -> StepUp
min :: StepUp -> StepUp -> StepUp
Ord, ReadPrec [StepUp]
ReadPrec StepUp
Int -> ReadS StepUp
ReadS [StepUp]
(Int -> ReadS StepUp)
-> ReadS [StepUp]
-> ReadPrec StepUp
-> ReadPrec [StepUp]
-> Read StepUp
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StepUp
readsPrec :: Int -> ReadS StepUp
$creadList :: ReadS [StepUp]
readList :: ReadS [StepUp]
$creadPrec :: ReadPrec StepUp
readPrec :: ReadPrec StepUp
$creadListPrec :: ReadPrec [StepUp]
readListPrec :: ReadPrec [StepUp]
Read)
data OriginalInfo = OriginalInfo {
OriginalInfo -> Balance
originBalance::Balance
,OriginalInfo -> Date
originDate::Date
,OriginalInfo -> Rational
originRate::Rate
,OriginalInfo -> Maybe Date
maturityDate :: Maybe Date
} deriving (Int -> OriginalInfo -> ShowS
[OriginalInfo] -> ShowS
OriginalInfo -> String
(Int -> OriginalInfo -> ShowS)
-> (OriginalInfo -> String)
-> ([OriginalInfo] -> ShowS)
-> Show OriginalInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OriginalInfo -> ShowS
showsPrec :: Int -> OriginalInfo -> ShowS
$cshow :: OriginalInfo -> String
show :: OriginalInfo -> String
$cshowList :: [OriginalInfo] -> ShowS
showList :: [OriginalInfo] -> ShowS
Show, OriginalInfo -> OriginalInfo -> Bool
(OriginalInfo -> OriginalInfo -> Bool)
-> (OriginalInfo -> OriginalInfo -> Bool) -> Eq OriginalInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OriginalInfo -> OriginalInfo -> Bool
== :: OriginalInfo -> OriginalInfo -> Bool
$c/= :: OriginalInfo -> OriginalInfo -> Bool
/= :: OriginalInfo -> OriginalInfo -> Bool
Eq, (forall x. OriginalInfo -> Rep OriginalInfo x)
-> (forall x. Rep OriginalInfo x -> OriginalInfo)
-> Generic OriginalInfo
forall x. Rep OriginalInfo x -> OriginalInfo
forall x. OriginalInfo -> Rep OriginalInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OriginalInfo -> Rep OriginalInfo x
from :: forall x. OriginalInfo -> Rep OriginalInfo x
$cto :: forall x. Rep OriginalInfo x -> OriginalInfo
to :: forall x. Rep OriginalInfo x -> OriginalInfo
Generic, Eq OriginalInfo
Eq OriginalInfo =>
(OriginalInfo -> OriginalInfo -> Ordering)
-> (OriginalInfo -> OriginalInfo -> Bool)
-> (OriginalInfo -> OriginalInfo -> Bool)
-> (OriginalInfo -> OriginalInfo -> Bool)
-> (OriginalInfo -> OriginalInfo -> Bool)
-> (OriginalInfo -> OriginalInfo -> OriginalInfo)
-> (OriginalInfo -> OriginalInfo -> OriginalInfo)
-> Ord OriginalInfo
OriginalInfo -> OriginalInfo -> Bool
OriginalInfo -> OriginalInfo -> Ordering
OriginalInfo -> OriginalInfo -> OriginalInfo
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 :: OriginalInfo -> OriginalInfo -> Ordering
compare :: OriginalInfo -> OriginalInfo -> Ordering
$c< :: OriginalInfo -> OriginalInfo -> Bool
< :: OriginalInfo -> OriginalInfo -> Bool
$c<= :: OriginalInfo -> OriginalInfo -> Bool
<= :: OriginalInfo -> OriginalInfo -> Bool
$c> :: OriginalInfo -> OriginalInfo -> Bool
> :: OriginalInfo -> OriginalInfo -> Bool
$c>= :: OriginalInfo -> OriginalInfo -> Bool
>= :: OriginalInfo -> OriginalInfo -> Bool
$cmax :: OriginalInfo -> OriginalInfo -> OriginalInfo
max :: OriginalInfo -> OriginalInfo -> OriginalInfo
$cmin :: OriginalInfo -> OriginalInfo -> OriginalInfo
min :: OriginalInfo -> OriginalInfo -> OriginalInfo
Ord, ReadPrec [OriginalInfo]
ReadPrec OriginalInfo
Int -> ReadS OriginalInfo
ReadS [OriginalInfo]
(Int -> ReadS OriginalInfo)
-> ReadS [OriginalInfo]
-> ReadPrec OriginalInfo
-> ReadPrec [OriginalInfo]
-> Read OriginalInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OriginalInfo
readsPrec :: Int -> ReadS OriginalInfo
$creadList :: ReadS [OriginalInfo]
readList :: ReadS [OriginalInfo]
$creadPrec :: ReadPrec OriginalInfo
readPrec :: ReadPrec OriginalInfo
$creadListPrec :: ReadPrec [OriginalInfo]
readListPrec :: ReadPrec [OriginalInfo]
Read)
type PlannedAmorSchedule = Ts
data BondType = Sequential
| PAC PlannedAmorSchedule
| AmtByPeriod (PerCurve Balance)
| PacAnchor PlannedAmorSchedule [BondName]
| Lockout Date
| IO
| Z
| Equity
deriving (Int -> BondType -> ShowS
[BondType] -> ShowS
BondType -> String
(Int -> BondType -> ShowS)
-> (BondType -> String) -> ([BondType] -> ShowS) -> Show BondType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BondType -> ShowS
showsPrec :: Int -> BondType -> ShowS
$cshow :: BondType -> String
show :: BondType -> String
$cshowList :: [BondType] -> ShowS
showList :: [BondType] -> ShowS
Show, BondType -> BondType -> Bool
(BondType -> BondType -> Bool)
-> (BondType -> BondType -> Bool) -> Eq BondType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BondType -> BondType -> Bool
== :: BondType -> BondType -> Bool
$c/= :: BondType -> BondType -> Bool
/= :: BondType -> BondType -> Bool
Eq, (forall x. BondType -> Rep BondType x)
-> (forall x. Rep BondType x -> BondType) -> Generic BondType
forall x. Rep BondType x -> BondType
forall x. BondType -> Rep BondType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BondType -> Rep BondType x
from :: forall x. BondType -> Rep BondType x
$cto :: forall x. Rep BondType x -> BondType
to :: forall x. Rep BondType x -> BondType
Generic, Eq BondType
Eq BondType =>
(BondType -> BondType -> Ordering)
-> (BondType -> BondType -> Bool)
-> (BondType -> BondType -> Bool)
-> (BondType -> BondType -> Bool)
-> (BondType -> BondType -> Bool)
-> (BondType -> BondType -> BondType)
-> (BondType -> BondType -> BondType)
-> Ord BondType
BondType -> BondType -> Bool
BondType -> BondType -> Ordering
BondType -> BondType -> BondType
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 :: BondType -> BondType -> Ordering
compare :: BondType -> BondType -> Ordering
$c< :: BondType -> BondType -> Bool
< :: BondType -> BondType -> Bool
$c<= :: BondType -> BondType -> Bool
<= :: BondType -> BondType -> Bool
$c> :: BondType -> BondType -> Bool
> :: BondType -> BondType -> Bool
$c>= :: BondType -> BondType -> Bool
>= :: BondType -> BondType -> Bool
$cmax :: BondType -> BondType -> BondType
max :: BondType -> BondType -> BondType
$cmin :: BondType -> BondType -> BondType
min :: BondType -> BondType -> BondType
Ord, ReadPrec [BondType]
ReadPrec BondType
Int -> ReadS BondType
ReadS [BondType]
(Int -> ReadS BondType)
-> ReadS [BondType]
-> ReadPrec BondType
-> ReadPrec [BondType]
-> Read BondType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BondType
readsPrec :: Int -> ReadS BondType
$creadList :: ReadS [BondType]
readList :: ReadS [BondType]
$creadPrec :: ReadPrec BondType
readPrec :: ReadPrec BondType
$creadListPrec :: ReadPrec [BondType]
readListPrec :: ReadPrec [BondType]
Read)
data Bond = Bond {
Bond -> String
bndName :: String
,Bond -> BondType
bndType :: BondType
,Bond -> OriginalInfo
bndOriginInfo :: OriginalInfo
,Bond -> InterestInfo
bndInterestInfo :: InterestInfo
,Bond -> Maybe StepUp
bndStepUp :: Maybe StepUp
,Bond -> Balance
bndBalance :: Balance
,Bond -> Spread
bndRate :: IRate
,Bond -> Balance
bndDuePrin :: Balance
,Bond -> Balance
bndDueInt :: Balance
,Bond -> Balance
bndDueIntOverInt :: Balance
,Bond -> Maybe Date
bndDueIntDate :: Maybe Date
,Bond -> Maybe Date
bndLastIntPay :: Maybe Date
,Bond -> Maybe Date
bndLastPrinPay :: Maybe Date
,Bond -> Maybe Statement
bndStmt :: Maybe S.Statement
}
| MultiIntBond {
bndName :: String
,bndType :: BondType
,bndOriginInfo :: OriginalInfo
,Bond -> [InterestInfo]
bndInterestInfos :: [InterestInfo]
,Bond -> Maybe [StepUp]
bndStepUps :: Maybe [StepUp]
,bndBalance :: Balance
,Bond -> [Spread]
bndRates :: [IRate]
,bndDuePrin :: Balance
,Bond -> [Balance]
bndDueInts :: [Balance]
,Bond -> [Balance]
bndDueIntOverInts :: [Balance]
,bndDueIntDate :: Maybe Date
,Bond -> Maybe [Date]
bndLastIntPays :: Maybe [Date]
,bndLastPrinPay :: Maybe Date
,bndStmt :: Maybe S.Statement
}
| BondGroup (Map.Map String Bond) (Maybe BondType)
deriving (Int -> Bond -> ShowS
[Bond] -> ShowS
Bond -> String
(Int -> Bond -> ShowS)
-> (Bond -> String) -> ([Bond] -> ShowS) -> Show Bond
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Bond -> ShowS
showsPrec :: Int -> Bond -> ShowS
$cshow :: Bond -> String
show :: Bond -> String
$cshowList :: [Bond] -> ShowS
showList :: [Bond] -> ShowS
Show, Bond -> Bond -> Bool
(Bond -> Bond -> Bool) -> (Bond -> Bond -> Bool) -> Eq Bond
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Bond -> Bond -> Bool
== :: Bond -> Bond -> Bool
$c/= :: Bond -> Bond -> Bool
/= :: Bond -> Bond -> Bool
Eq, (forall x. Bond -> Rep Bond x)
-> (forall x. Rep Bond x -> Bond) -> Generic Bond
forall x. Rep Bond x -> Bond
forall x. Bond -> Rep Bond x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Bond -> Rep Bond x
from :: forall x. Bond -> Rep Bond x
$cto :: forall x. Rep Bond x -> Bond
to :: forall x. Rep Bond x -> Bond
Generic, Eq Bond
Eq Bond =>
(Bond -> Bond -> Ordering)
-> (Bond -> Bond -> Bool)
-> (Bond -> Bond -> Bool)
-> (Bond -> Bond -> Bool)
-> (Bond -> Bond -> Bool)
-> (Bond -> Bond -> Bond)
-> (Bond -> Bond -> Bond)
-> Ord Bond
Bond -> Bond -> Bool
Bond -> Bond -> Ordering
Bond -> Bond -> Bond
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 :: Bond -> Bond -> Ordering
compare :: Bond -> Bond -> Ordering
$c< :: Bond -> Bond -> Bool
< :: Bond -> Bond -> Bool
$c<= :: Bond -> Bond -> Bool
<= :: Bond -> Bond -> Bool
$c> :: Bond -> Bond -> Bool
> :: Bond -> Bond -> Bool
$c>= :: Bond -> Bond -> Bool
>= :: Bond -> Bond -> Bool
$cmax :: Bond -> Bond -> Bond
max :: Bond -> Bond -> Bond
$cmin :: Bond -> Bond -> Bond
min :: Bond -> Bond -> Bond
Ord, ReadPrec [Bond]
ReadPrec Bond
Int -> ReadS Bond
ReadS [Bond]
(Int -> ReadS Bond)
-> ReadS [Bond] -> ReadPrec Bond -> ReadPrec [Bond] -> Read Bond
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Bond
readsPrec :: Int -> ReadS Bond
$creadList :: ReadS [Bond]
readList :: ReadS [Bond]
$creadPrec :: ReadPrec Bond
readPrec :: ReadPrec Bond
$creadListPrec :: ReadPrec [Bond]
readListPrec :: ReadPrec [Bond]
Read)
interestInfoTraversal :: Traversal' Bond InterestInfo
interestInfoTraversal :: Traversal' Bond InterestInfo
interestInfoTraversal InterestInfo -> f InterestInfo
f (Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
ii Maybe StepUp
su Balance
bal Spread
r Balance
dp Balance
di Balance
dioi Maybe Date
did Maybe Date
lip Maybe Date
lpp Maybe Statement
stmt)
= (\InterestInfo
ii' -> String
-> BondType
-> OriginalInfo
-> InterestInfo
-> Maybe StepUp
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Date
-> Maybe Date
-> Maybe Date
-> Maybe Statement
-> Bond
Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
ii' Maybe StepUp
su Balance
bal Spread
r Balance
dp Balance
di Balance
dioi Maybe Date
did Maybe Date
lip Maybe Date
lpp Maybe Statement
stmt) (InterestInfo -> Bond) -> f InterestInfo -> f Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InterestInfo -> f InterestInfo
f InterestInfo
ii
interestInfoTraversal InterestInfo -> f InterestInfo
f (MultiIntBond String
bn BondType
bt OriginalInfo
oi [InterestInfo]
iis Maybe [StepUp]
sus Balance
bal [Spread]
rs Balance
dp [Balance]
dis [Balance]
diois Maybe Date
did Maybe [Date]
lips Maybe Date
lpp Maybe Statement
stmt)
= (\[InterestInfo]
iis' -> String
-> BondType
-> OriginalInfo
-> [InterestInfo]
-> Maybe [StepUp]
-> Balance
-> [Spread]
-> Balance
-> [Balance]
-> [Balance]
-> Maybe Date
-> Maybe [Date]
-> Maybe Date
-> Maybe Statement
-> Bond
MultiIntBond String
bn BondType
bt OriginalInfo
oi [InterestInfo]
iis' Maybe [StepUp]
sus Balance
bal [Spread]
rs Balance
dp [Balance]
dis [Balance]
diois Maybe Date
did Maybe [Date]
lips Maybe Date
lpp Maybe Statement
stmt) ([InterestInfo] -> Bond) -> f [InterestInfo] -> f Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (InterestInfo -> f InterestInfo)
-> [InterestInfo] -> f [InterestInfo]
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 InterestInfo -> f InterestInfo
f [InterestInfo]
iis
interestInfoTraversal InterestInfo -> f InterestInfo
f (BondGroup Map String Bond
bMap Maybe BondType
x)
= Map String Bond -> Maybe BondType -> Bond
BondGroup (Map String Bond -> Maybe BondType -> Bond)
-> f (Map String Bond) -> f (Maybe BondType -> Bond)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Bond -> f Bond) -> Map String Bond -> f (Map String Bond)
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 ((InterestInfo -> f InterestInfo) -> Bond -> f Bond
Traversal' Bond InterestInfo
interestInfoTraversal InterestInfo -> f InterestInfo
f) Map String Bond
bMap f (Maybe BondType -> Bond) -> f (Maybe BondType) -> f Bond
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BondType -> f (Maybe BondType)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe BondType
x
curRatesTraversal :: Traversal' Bond IRate
curRatesTraversal :: Traversal' Bond Spread
curRatesTraversal Spread -> f Spread
f (Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
ii Maybe StepUp
su Balance
bal Spread
r Balance
dp Balance
di Balance
dioi Maybe Date
did Maybe Date
lip Maybe Date
lpp Maybe Statement
stmt)
= (\Spread
r' -> String
-> BondType
-> OriginalInfo
-> InterestInfo
-> Maybe StepUp
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Date
-> Maybe Date
-> Maybe Date
-> Maybe Statement
-> Bond
Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
ii Maybe StepUp
su Balance
bal Spread
r' Balance
dp Balance
di Balance
dioi Maybe Date
did Maybe Date
lip Maybe Date
lpp Maybe Statement
stmt) (Spread -> Bond) -> f Spread -> f Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Spread -> f Spread
f Spread
r
curRatesTraversal Spread -> f Spread
f (MultiIntBond String
bn BondType
bt OriginalInfo
oi [InterestInfo]
iis Maybe [StepUp]
sus Balance
bal [Spread]
rs Balance
dp [Balance]
dis [Balance]
diois Maybe Date
did Maybe [Date]
lips Maybe Date
lpp Maybe Statement
stmt)
= (\[Spread]
rs' -> String
-> BondType
-> OriginalInfo
-> [InterestInfo]
-> Maybe [StepUp]
-> Balance
-> [Spread]
-> Balance
-> [Balance]
-> [Balance]
-> Maybe Date
-> Maybe [Date]
-> Maybe Date
-> Maybe Statement
-> Bond
MultiIntBond String
bn BondType
bt OriginalInfo
oi [InterestInfo]
iis Maybe [StepUp]
sus Balance
bal [Spread]
rs' Balance
dp [Balance]
dis [Balance]
diois Maybe Date
did Maybe [Date]
lips Maybe Date
lpp Maybe Statement
stmt) ([Spread] -> Bond) -> f [Spread] -> f Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Spread -> f Spread) -> [Spread] -> f [Spread]
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 Spread -> f Spread
f [Spread]
rs
curRatesTraversal Spread -> f Spread
f (BondGroup Map String Bond
bMap Maybe BondType
x)
= Map String Bond -> Maybe BondType -> Bond
BondGroup (Map String Bond -> Maybe BondType -> Bond)
-> f (Map String Bond) -> f (Maybe BondType -> Bond)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Bond -> f Bond) -> Map String Bond -> f (Map String Bond)
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 ((Spread -> f Spread) -> Bond -> f Bond
Traversal' Bond Spread
curRatesTraversal Spread -> f Spread
f) Map String Bond
bMap f (Maybe BondType -> Bond) -> f (Maybe BondType) -> f Bond
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe BondType -> f (Maybe BondType)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe BondType
x
adjustBalance :: Balance -> Bond -> Bond
adjustBalance :: Balance -> Bond -> Bond
adjustBalance Balance
bal b :: Bond
b@Bond{bndBalance :: Bond -> Balance
bndBalance = Balance
_, bndOriginInfo :: Bond -> OriginalInfo
bndOriginInfo = OriginalInfo
oi }
= Bond
b {bndBalance = bal, bndOriginInfo = oi {originBalance = bal}}
bndmStmt :: Lens' Bond (Maybe S.Statement)
bndmStmt :: Lens' Bond (Maybe Statement)
bndmStmt = (Bond -> Maybe Statement)
-> (Bond -> Maybe Statement -> Bond)
-> Lens' Bond (Maybe Statement)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Bond -> Maybe Statement
getter Bond -> Maybe Statement -> Bond
setter
where
getter :: Bond -> Maybe Statement
getter Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
mStmt} = Maybe Statement
mStmt
getter MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
mStmt} = Maybe Statement
mStmt
setter :: Bond -> Maybe Statement -> Bond
setter Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
_} Maybe Statement
mStmt = Bond{bndStmt :: Maybe Statement
bndStmt = Maybe Statement
mStmt}
setter MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
_} Maybe Statement
mStmt = MultiIntBond{bndStmt :: Maybe Statement
bndStmt = Maybe Statement
mStmt}
bondCashflow :: Bond -> ([Date], [Amount])
bondCashflow :: Bond -> ([Date], [Balance])
bondCashflow Bond
b =
let t :: [Txn]
t = Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns Bond
b
in
(Txn -> Date
forall ts. TimeSeries ts => ts -> Date
S.getDate (Txn -> Date) -> [Txn] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
t, Txn -> Balance
S.getTxnAmt (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
t)
consolStmt :: Bond -> Bond
consolStmt :: Bond -> Bond
consolStmt (BondGroup Map String Bond
bMap Maybe BondType
x) = Map String Bond -> Maybe BondType -> Bond
BondGroup (Bond -> Bond
consolStmt (Bond -> Bond) -> Map String Bond -> Map String Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond
bMap) Maybe BondType
x
consolStmt Bond
b
| Bond -> Bool
forall a. HasStmt a => a -> Bool
S.hasEmptyTxn Bond
b = Bond
b
| Bool
otherwise = let
Txn
txn:[Txn]
txns = Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns Bond
b
combinedBondTxns :: [Txn]
combinedBondTxns = ([Txn] -> Txn -> [Txn]) -> [Txn] -> [Txn] -> [Txn]
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl [Txn] -> Txn -> [Txn]
S.consolTxn [Txn
txn] [Txn]
txns
droppedTxns :: [Txn]
droppedTxns = (Txn -> Bool) -> [Txn] -> [Txn]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Txn -> Bool
S.isEmptyTxn [Txn]
combinedBondTxns
in
Bond
b {bndStmt = Just (S.Statement (DL.fromList (reverse droppedTxns)))}
setBondOrigDate :: Date -> Bond -> Bond
setBondOrigDate :: Date -> Bond -> Bond
setBondOrigDate Date
d b :: Bond
b@Bond{bndOriginInfo :: Bond -> OriginalInfo
bndOriginInfo = OriginalInfo
oi} = Bond
b {bndOriginInfo = oi{originDate = d}}
setBondOrigDate Date
d b :: Bond
b@MultiIntBond{bndOriginInfo :: Bond -> OriginalInfo
bndOriginInfo = OriginalInfo
oi} = Bond
b {bndOriginInfo = oi{originDate = d}}
setBondOrigDate Date
d (BondGroup Map String Bond
bMap Maybe BondType
x) = Map String Bond -> Maybe BondType -> Bond
BondGroup ((Date -> Bond -> Bond
setBondOrigDate Date
d) (Bond -> Bond) -> Map String Bond -> Map String Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond
bMap) (Maybe BondType -> Bond) -> Maybe BondType -> Bond
forall a b. (a -> b) -> a -> b
$ Maybe BondType
x
patchBondFactor :: Bond -> Bond
patchBondFactor :: Bond -> Bond
patchBondFactor (BondGroup Map String Bond
bMap Maybe BondType
x) = Map String Bond -> Maybe BondType -> Bond
BondGroup (Bond -> Bond
patchBondFactor (Bond -> Bond) -> Map String Bond -> Map String Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond
bMap) (Maybe BondType -> Bond) -> Maybe BondType -> Bond
forall a b. (a -> b) -> a -> b
$ Maybe BondType
x
patchBondFactor Bond
bnd
| Bond -> Bool
forall a. HasStmt a => a -> Bool
S.hasEmptyTxn Bond
bnd = Bond
bnd
| (OriginalInfo -> Balance
originBalance (Bond -> OriginalInfo
bndOriginInfo Bond
bnd)) Balance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
== Balance
0 = Bond
bnd
| Bool
otherwise = let
oBal :: Balance
oBal = OriginalInfo -> Balance
originBalance (Bond -> OriginalInfo
bndOriginInfo Bond
bnd)
toFactor :: Txn -> Txn
toFactor (BondTxn Date
d Balance
b Balance
i Balance
p Spread
r0 Balance
c Balance
e Balance
f Maybe Float
Nothing TxnComment
t) = (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
b Balance
i Balance
p Spread
r0 Balance
c Balance
e Balance
f (Float -> Maybe Float
forall a. a -> Maybe a
Just (Rational -> Float
forall a. Fractional a => Rational -> a
fromRational (Balance -> Balance -> Rational
divideBB Balance
b Balance
oBal))) TxnComment
t)
newBnd :: Bond
newBnd = case Bond -> Maybe Statement
bndStmt Bond
bnd of
Maybe Statement
Nothing -> Bond
bnd
Just (S.Statement DList Txn
txns) -> Bond
bnd {bndStmt = Just (S.Statement (toFactor <$> txns)) }
in
Bond
newBnd
payInt :: Date -> Amount -> Bond -> Bond
payInt :: Date -> Balance -> Bond -> Bond
payInt Date
d Balance
0 Bond
b = Bond
b
payInt Date
d Balance
amt bnd :: Bond
bnd@(Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
iinfo Maybe StepUp
_ Balance
bal Spread
r Balance
duePrin Balance
dueInt Balance
dueIoI Maybe Date
dueIntDate Maybe Date
lpayInt Maybe Date
lpayPrin Maybe Statement
stmt)
= Bond
bnd {bndDueInt=newDue, bndStmt=newStmt, bndLastIntPay = Just d, bndDueIntOverInt = newDueIoI}
where
rs :: [Balance]
rs = Balance -> [Balance] -> [Balance]
Lib.paySeqLiabilitiesAmt Balance
amt [Balance
dueIoI, Balance
dueInt]
newDueIoI :: Balance
newDueIoI = Balance
dueIoI Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- [Balance] -> Balance
forall a. HasCallStack => [a] -> a
head [Balance]
rs
newDue :: Balance
newDue = Balance
dueInt Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- [Balance]
rs [Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!! Int
1
newStmt :: Maybe Statement
newStmt = case BondType
bt of
BondType
Equity -> Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
bal Balance
amt Balance
0 Spread
r Balance
amt Balance
newDue Balance
newDueIoI Maybe Float
forall a. Maybe a
Nothing (String -> TxnComment
S.PayYield String
bn)) Maybe Statement
stmt
BondType
_ -> Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
bal Balance
amt Balance
0 Spread
r Balance
amt Balance
newDue Balance
newDueIoI Maybe Float
forall a. Maybe a
Nothing ([String] -> TxnComment
S.PayInt [String
bn])) Maybe Statement
stmt
payInt Date
d Balance
amt bnd :: Bond
bnd@(MultiIntBond String
bn BondType
bt OriginalInfo
oi [InterestInfo]
iinfo Maybe [StepUp]
_ Balance
bal [Spread]
rs Balance
duePrin [Balance]
dueInts [Balance]
dueIoIs Maybe Date
dueIntDate Maybe [Date]
lpayInt Maybe Date
lpayPrin Maybe Statement
stmt)
= Bond
bnd {bndDueInts=newDues, bndStmt=newStmt
, bndLastIntPays = Just (replicate l d), bndDueIntOverInts = newDueIoIs}
where
l :: Int
l = [InterestInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [InterestInfo]
iinfo
ioiPaid :: [Balance]
ioiPaid = Balance -> [Balance] -> [Balance]
Lib.paySeqLiabilitiesAmt Balance
amt [Balance]
dueIoIs
afterIoI :: Balance
afterIoI = Balance
amt Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
ioiPaid
duePaid :: [Balance]
duePaid = Balance -> [Balance] -> [Balance]
Lib.paySeqLiabilitiesAmt Balance
afterIoI [Balance]
dueInts
newDueIoIs :: [Balance]
newDueIoIs = (Balance -> Balance -> Balance)
-> [Balance] -> [Balance] -> [Balance]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [Balance]
dueIoIs [Balance]
ioiPaid
newDues :: [Balance]
newDues = (Balance -> Balance -> Balance)
-> [Balance] -> [Balance] -> [Balance]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [Balance]
dueInts [Balance]
duePaid
newDueIoI :: Balance
newDueIoI = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
newDueIoIs
newDue :: Balance
newDue = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
newDues
newStmt :: Maybe Statement
newStmt = case BondType
bt of
BondType
Equity -> Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
bal Balance
amt Balance
0 ([Spread] -> Spread
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Spread]
rs) Balance
amt Balance
newDue Balance
newDueIoI Maybe Float
forall a. Maybe a
Nothing (String -> TxnComment
S.PayYield String
bn)) Maybe Statement
stmt
BondType
_ -> Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
bal Balance
amt Balance
0 ([Spread] -> Spread
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Spread]
rs) Balance
amt Balance
newDue Balance
newDueIoI Maybe Float
forall a. Maybe a
Nothing ([String] -> TxnComment
S.PayInt [String
bn])) Maybe Statement
stmt
payIntByIndex :: Date -> Int -> Amount -> Bond -> Bond
payIntByIndex :: Date -> Int -> Balance -> Bond -> Bond
payIntByIndex Date
d Int
_ Balance
0 Bond
b = Bond
b
payIntByIndex Date
d Int
idx Balance
amt bnd :: Bond
bnd@(MultiIntBond String
bn BondType
bt OriginalInfo
oi [InterestInfo]
iinfo Maybe [StepUp]
_ Balance
bal [Spread]
rs Balance
duePrin [Balance]
dueInts [Balance]
dueIoIs Maybe Date
dueIntDate Maybe [Date]
lpayInt Maybe Date
lpayPrin Maybe Statement
stmt)
= let
dueIoI :: Balance
dueIoI = [Balance]
dueIoIs [Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!! Int
idx
dueInt :: Balance
dueInt = [Balance]
dueInts [Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!! Int
idx
[Balance
newDueIoI,Balance
newDue] = Balance -> [Balance] -> [Balance]
Lib.paySeqLiabResi Balance
amt [Balance
dueIoI, Balance
dueInt]
newStmt :: Maybe Statement
newStmt = Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
bal Balance
amt Balance
0 ([Spread] -> Spread
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Spread]
rs) Balance
amt Balance
newDue Balance
newDueIoI Maybe Float
forall a. Maybe a
Nothing ([String] -> TxnComment
S.PayInt [String
bn])) Maybe Statement
stmt
od :: Date
od = Bond -> Date
forall lb. Liable lb => lb -> Date
getOriginDate Bond
bnd
ods :: [Date]
ods = Int -> Date -> [Date]
forall a. Int -> a -> [a]
replicate ([InterestInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [InterestInfo]
iinfo) Date
od
in
Bond
bnd {bndDueInts = dueInts & ix idx .~ newDue
,bndDueIntOverInts = dueIoIs & ix idx .~ newDueIoI
,bndStmt = newStmt
,bndLastIntPays = case lpayInt of
Maybe [Date]
Nothing -> [Date] -> Maybe [Date]
forall a. a -> Maybe a
Just ([Date] -> Maybe [Date]) -> [Date] -> Maybe [Date]
forall a b. (a -> b) -> a -> b
$ [Date]
ods [Date] -> ([Date] -> [Date]) -> [Date]
forall a b. a -> (a -> b) -> b
& Index [Date] -> Traversal' [Date] (IxValue [Date])
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
Index [Date]
idx ((Date -> Identity Date) -> [Date] -> Identity [Date])
-> Date -> [Date] -> [Date]
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Date
d
Just [Date]
ds -> [Date] -> Maybe [Date]
forall a. a -> Maybe a
Just ([Date] -> Maybe [Date]) -> [Date] -> Maybe [Date]
forall a b. (a -> b) -> a -> b
$ [Date]
ds [Date] -> ([Date] -> [Date]) -> [Date]
forall a b. a -> (a -> b) -> b
& Index [Date] -> Traversal' [Date] (IxValue [Date])
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
Index [Date]
idx ((Date -> Identity Date) -> [Date] -> Identity [Date])
-> Date -> [Date] -> [Date]
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Date
d}
payYield :: Date -> Amount -> Bond -> Bond
payYield :: Date -> Balance -> Bond -> Bond
payYield Date
d Balance
amt bnd :: Bond
bnd@(Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
iinfo Maybe StepUp
_ Balance
bal Spread
r Balance
duePrin Balance
dueInt Balance
dueIoI Maybe Date
dueIntDate Maybe Date
lpayInt Maybe Date
lpayPrin Maybe Statement
stmt)
= Bond
bnd {bndDueInt = newDue,bndDueIntOverInt=newDueIoI, bndStmt= newStmt}
where
[Balance
newDue,Balance
newDueIoI] = Balance -> [Balance] -> [Balance]
paySeqLiabResi Balance
amt [Balance
dueIoI, Balance
dueInt]
newStmt :: Maybe Statement
newStmt = Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
bal Balance
amt Balance
0 Spread
r Balance
amt Balance
newDue Balance
newDueIoI Maybe Float
forall a. Maybe a
Nothing (String -> TxnComment
S.PayYield String
bn)) Maybe Statement
stmt
payPrin :: Date -> Amount -> Bond -> Bond
payPrin :: Date -> Balance -> Bond -> Bond
payPrin Date
d Balance
0 Bond
bnd = Bond
bnd
payPrin Date
d Balance
_ bnd :: Bond
bnd@(Bond String
bn BondType
bt OriginalInfo
oi InterestInfo
iinfo Maybe StepUp
_ Balance
0 Spread
r Balance
0 Balance
0 Balance
dueIoI Maybe Date
dueIntDate Maybe Date
lpayInt Maybe Date
lpayPrin Maybe Statement
stmt) = Bond
bnd
payPrin Date
d Balance
amt Bond
bnd = Bond
bnd {bndDuePrin =newDue, bndBalance = newBal , bndStmt=newStmt}
where
newBal :: Balance
newBal = (Bond -> Balance
bndBalance Bond
bnd) Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
amt
newDue :: Balance
newDue = (Bond -> Balance
bndDuePrin Bond
bnd) Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
amt
bn :: String
bn = Bond -> String
bndName Bond
bnd
stmt :: Maybe Statement
stmt = Bond -> Maybe Statement
bndStmt Bond
bnd
dueIoI :: Balance
dueIoI = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueIntOverInt Bond
bnd
dueInt :: Balance
dueInt = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueInt Bond
bnd
r :: Spread
r = Bond -> Spread
forall lb. Liable lb => lb -> Spread
getCurRate Bond
bnd
newStmt :: Maybe Statement
newStmt = Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
newBal Balance
0 Balance
amt Spread
r Balance
amt Balance
dueInt Balance
dueIoI Maybe Float
forall a. Maybe a
Nothing ([String] -> TxnComment
S.PayPrin [String
bn] )) Maybe Statement
stmt
writeOff :: Date -> Amount -> Bond -> Either String Bond
writeOff :: Date -> Balance -> Bond -> Either String Bond
writeOff Date
d Balance
0 Bond
b = Bond -> Either String Bond
forall a b. b -> Either a b
Right Bond
b
writeOff Date
d Balance
amt Bond
_bnd
| Bond -> Balance
bndBalance Bond
_bnd Balance -> Balance -> Bool
forall a. Ord a => a -> a -> Bool
< Balance
amt = String -> Either String Bond
forall a b. a -> Either a b
Left (String -> Either String Bond) -> String -> Either String Bond
forall a b. (a -> b) -> a -> b
$ String
"Insufficient balance to write off "String -> ShowS
forall a. [a] -> [a] -> [a]
++ Balance -> String
forall a. Show a => a -> String
show Balance
amt String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
" bond name "String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Bond -> String
bndName Bond
_bnd)
| Bool
otherwise =
let
bnd :: Bond
bnd = Date -> Bond -> Bond
accrueInt Date
d Bond
_bnd
newBal :: Balance
newBal = Bond -> Balance
bndBalance Bond
bnd Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
amt
dueIoI :: Balance
dueIoI = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueIntOverInt Bond
bnd
dueInt :: Balance
dueInt = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueInt Bond
bnd
bn :: String
bn = Bond -> String
bndName Bond
bnd
stmt :: Maybe Statement
stmt = Bond -> Maybe Statement
bndStmt Bond
bnd
newStmt :: Maybe Statement
newStmt = Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
newBal Balance
0 Balance
0 Spread
0 Balance
0 Balance
dueInt Balance
dueIoI Maybe Float
forall a. Maybe a
Nothing (String -> Balance -> TxnComment
S.WriteOff String
bn Balance
amt )) Maybe Statement
stmt
in
Bond -> Either String Bond
forall a b. b -> Either a b
Right (Bond -> Either String Bond) -> Bond -> Either String Bond
forall a b. (a -> b) -> a -> b
$ Bond
bnd {bndBalance = newBal , bndStmt=newStmt}
fundWith :: Date -> Amount -> Bond -> Bond
fundWith :: Date -> Balance -> Bond -> Bond
fundWith Date
d Balance
0 Bond
b = Bond
b
fundWith Date
d Balance
amt Bond
_bnd = Bond
bnd {bndBalance = newBal, bndStmt=newStmt }
where
bnd :: Bond
bnd = Date -> Bond -> Bond
accrueInt Date
d Bond
_bnd
dueIoI :: Balance
dueIoI = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueIntOverInt Bond
bnd
dueInt :: Balance
dueInt = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueInt Bond
bnd
bn :: String
bn = Bond -> String
bndName Bond
bnd
stmt :: Maybe Statement
stmt = Bond -> Maybe Statement
bndStmt Bond
bnd
newBal :: Balance
newBal = Bond -> Balance
bndBalance Bond
bnd Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
amt
newStmt :: Maybe Statement
newStmt = Txn -> Maybe Statement -> Maybe Statement
S.appendStmt (Date
-> Balance
-> Balance
-> Balance
-> Spread
-> Balance
-> Balance
-> Balance
-> Maybe Float
-> TxnComment
-> Txn
BondTxn Date
d Balance
newBal Balance
0 (Balance -> Balance
forall a. Num a => a -> a
negate Balance
amt) Spread
0 Balance
0 Balance
dueInt Balance
dueIoI Maybe Float
forall a. Maybe a
Nothing (String -> Balance -> TxnComment
S.FundWith String
bn Balance
amt )) Maybe Statement
stmt
getIoI :: InterestInfo -> IRate -> IRate
getIoI :: InterestInfo -> Spread -> Spread
getIoI (WithIoI InterestInfo
_ (OverCurrRateBy Rational
r)) Spread
rate = Spread
rate Spread -> Spread -> Spread
forall a. Num a => a -> a -> a
* (Spread
1Spread -> Spread -> Spread
forall a. Num a => a -> a -> a
+ Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational Rational
r)
getIoI (WithIoI InterestInfo
_ (OverFixSpread Spread
r)) Spread
rate = Spread
rate Spread -> Spread -> Spread
forall a. Num a => a -> a -> a
+ Spread
r
getIoI InterestInfo
_ Spread
rate = Spread
rate
accrueInt :: Date -> Bond -> Bond
accrueInt :: Date -> Bond -> Bond
accrueInt Date
d b :: Bond
b@Bond{bndInterestInfo :: Bond -> InterestInfo
bndInterestInfo = InterestInfo
ii,bndDueIntDate :: Bond -> Maybe Date
bndDueIntDate = Maybe Date
mDueIntDate, bndDueInt :: Bond -> Balance
bndDueInt= Balance
dueInt
, bndDueIntOverInt :: Bond -> Balance
bndDueIntOverInt = Balance
dueIoI, bndRate :: Bond -> Spread
bndRate = Spread
r, bndBalance :: Bond -> Balance
bndBalance = Balance
bal}
| Date
d Date -> Date -> Bool
forall a. Eq a => a -> a -> Bool
== Date
beginDate = Bond
b
| Bool
otherwise = let
dc :: DayCount
dc = (DayCount -> Maybe DayCount -> DayCount
forall a. a -> Maybe a -> a
fromMaybe DayCount
DC_ACT_365F) (InterestInfo -> Maybe DayCount
getDayCountFromInfo InterestInfo
ii)
r2 :: Spread
r2 = InterestInfo -> Spread -> Spread
getIoI InterestInfo
ii Spread
r
period :: Rational
period = DayCount -> Date -> Date -> Rational
yearCountFraction DayCount
dc Date
beginDate Date
d
newDue :: Balance
newDue = Balance -> Date -> Date -> Spread -> DayCount -> Balance
IR.calcInt Balance
bal Date
beginDate Date
d Spread
r DayCount
dc
newIoiDue :: Balance
newIoiDue = Balance -> Rational -> Balance
mulBR Balance
dueInt (Spread -> Rational
forall a. Real a => a -> Rational
toRational Spread
r2 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
period)
in
Bond
b {bndDueInt = newDue+dueInt, bndDueIntOverInt = dueIoI+newIoiDue
,bndDueIntDate = Just d}
where
beginDate :: Date
beginDate = case Maybe Date
mDueIntDate of
Just Date
_d -> Date
_d
Maybe Date
Nothing -> Bond -> Date
forall lb. Liable lb => lb -> Date
getOriginDate Bond
b
accrueInt Date
d b :: Bond
b@MultiIntBond{bndInterestInfos :: Bond -> [InterestInfo]
bndInterestInfos = [InterestInfo]
iis, bndDueIntDate :: Bond -> Maybe Date
bndDueIntDate = Maybe Date
mDueIntDate
, bndDueInts :: Bond -> [Balance]
bndDueInts = [Balance]
dueInts, bndDueIntOverInts :: Bond -> [Balance]
bndDueIntOverInts = [Balance]
dueIoIs
, bndRates :: Bond -> [Spread]
bndRates = [Spread]
rs, bndBalance :: Bond -> Balance
bndBalance = Balance
bal}
| Date
beginDate Date -> Date -> Bool
forall a. Eq a => a -> a -> Bool
== Date
d = Bond
b
| Bool
otherwise
= let
l :: Int
l = [InterestInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [InterestInfo]
iis
daycounts :: [DayCount]
daycounts = (DayCount -> Maybe DayCount -> DayCount
forall a. a -> Maybe a -> a
fromMaybe DayCount
DC_ACT_365F) (Maybe DayCount -> DayCount)
-> (InterestInfo -> Maybe DayCount) -> InterestInfo -> DayCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterestInfo -> Maybe DayCount
getDayCountFromInfo (InterestInfo -> DayCount) -> [InterestInfo] -> [DayCount]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [InterestInfo]
iis
periods :: [Rational]
periods = (DayCount -> Date -> Date -> Rational)
-> [DayCount] -> [Date] -> [Date] -> [Rational]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 DayCount -> Date -> Date -> Rational
yearCountFraction [DayCount]
daycounts (Int -> Date -> [Date]
forall a. Int -> a -> [a]
replicate Int
l Date
beginDate) (Date -> [Date]
forall a. a -> [a]
repeat Date
d)
newDues :: [Balance]
newDues = (Spread -> Rational -> Balance -> Balance)
-> [Spread] -> [Rational] -> [Balance] -> [Balance]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 (\Spread
r Rational
p Balance
due -> (Balance -> Rational -> Balance
mulBR (Balance -> Spread -> Balance
mulBIR Balance
bal Spread
r) Rational
p) Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
due) [Spread]
rs [Rational]
periods [Balance]
dueInts
newIoiDues :: [Balance]
newIoiDues = (Spread
-> Rational -> Balance -> Balance -> InterestInfo -> Balance)
-> [Spread]
-> [Rational]
-> [Balance]
-> [Balance]
-> [InterestInfo]
-> [Balance]
forall a b c d e f.
(a -> b -> c -> d -> e -> f)
-> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
zipWith5 (\Spread
r Rational
p Balance
due Balance
dueIoI InterestInfo
ii ->
(Balance -> Rational -> Balance
mulBR (Balance -> Spread -> Balance
mulBIR Balance
due (InterestInfo -> Spread -> Spread
getIoI InterestInfo
ii Spread
r)) Rational
p) Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
dueIoI)
[Spread]
rs
[Rational]
periods
[Balance]
dueInts
[Balance]
dueIoIs
[InterestInfo]
iis
in
Bond
b {bndDueInts = newDues, bndDueIntOverInts = newIoiDues, bndDueIntDate = Just d }
where
l :: Int
l = [InterestInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [InterestInfo]
iis
beginDate :: Date
beginDate = case Maybe Date
mDueIntDate of
Just Date
ds -> Date
ds
Maybe Date
Nothing -> Bond -> Date
forall lb. Liable lb => lb -> Date
getOriginDate Bond
b
accrueInt Date
d (BondGroup Map String Bond
bMap Maybe BondType
x) = Map String Bond -> Maybe BondType -> Bond
BondGroup (Date -> Bond -> Bond
accrueInt Date
d (Bond -> Bond) -> Map String Bond -> Map String Bond
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond
bMap) (Maybe BondType -> Bond) -> Maybe BondType -> Bond
forall a b. (a -> b) -> a -> b
$ Maybe BondType
x
calcWalBond :: Date -> Bond -> Rational
calcWalBond :: Date -> Bond -> Rational
calcWalBond Date
d b :: Bond
b@Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} = Rational
0.0
calcWalBond Date
d b :: Bond
b@MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} = Rational
0.0
calcWalBond Date
d (BondGroup Map String Bond
bMap Maybe BondType
_)
= let
bndWal :: [Rational]
bndWal = Date -> Bond -> Rational
calcWalBond Date
d (Bond -> Rational) -> [Bond] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
bndBals :: [Rational]
bndBals = Balance -> Rational
forall a. Real a => a -> Rational
toRational (Balance -> Rational) -> (Bond -> Balance) -> Bond -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bond -> Balance
forall lb. Liable lb => lb -> Balance
getCurBalance (Bond -> Rational) -> [Bond] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
in
[Rational] -> [Rational] -> Rational
weightedBy [Rational]
bndBals [Rational]
bndWal
calcWalBond Date
d Bond
b
= let
txns :: [Txn]
txns = CutoffType -> DateDirection -> Date -> [Txn] -> [Txn]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Exc DateDirection
Future Date
d ([Txn] -> [Txn]) -> [Txn] -> [Txn]
forall a b. (a -> b) -> a -> b
$ Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns Bond
b
cutoffBalance :: Balance
cutoffBalance = (Txn -> Balance
S.getTxnBegBalance (Txn -> Balance) -> ([Txn] -> Txn) -> [Txn] -> Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Txn] -> Txn
forall a. HasCallStack => [a] -> a
head ) [Txn]
txns
lastBalance :: Balance
lastBalance = (Txn -> Balance
S.getTxnBalance (Txn -> Balance) -> ([Txn] -> Txn) -> [Txn] -> Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Txn] -> Txn
forall a. HasCallStack => [a] -> a
last) [Txn]
txns
firstTxnDate :: Date
firstTxnDate = Date
d
gapDays :: [Integer]
gapDays = (Date -> Date -> Integer
daysBetween Date
firstTxnDate) (Date -> Integer) -> (Txn -> Date) -> Txn -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Txn -> Date
forall ts. TimeSeries ts => ts -> Date
S.getDate (Txn -> Integer) -> [Txn] -> [Integer]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
txns
weightPrins :: [Balance]
weightPrins = (Balance -> Balance -> Balance)
-> [Balance] -> [Balance] -> [Balance]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
(*) (Txn -> Balance
S.getTxnPrincipal (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
txns) (Integer -> Balance
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Balance) -> [Integer] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer]
gapDays)
wal :: Balance
wal = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
weightPrins Balance -> Balance -> Balance
forall a. Fractional a => a -> a -> a
/ Balance
365 Balance -> Balance -> Balance
forall a. Fractional a => a -> a -> a
/ Balance
cutoffBalance
in
if Balance
lastBalance Balance -> Balance -> Bool
forall a. Ord a => a -> a -> Bool
> Balance
0 then
Rational
0
else
Balance -> Rational
forall a. Real a => a -> Rational
toRational Balance
wal
getTxnRate :: Txn -> IRate
getTxnRate :: Txn -> Spread
getTxnRate (BondTxn Date
_ Balance
_ Balance
_ Balance
_ Spread
r Balance
_ Balance
_ Balance
_ Maybe Float
_ TxnComment
_) = Spread
r
getTxnRate Txn
_ = Spread
0.0
getTxnInt :: Txn -> Amount
getTxnInt :: Txn -> Balance
getTxnInt (BondTxn Date
_ Balance
_ Balance
_ Balance
i Spread
_ Balance
_ Balance
_ Balance
_ Maybe Float
_ TxnComment
_) = Balance
i
getTxnInt Txn
_ = Balance
0.0
priceBond :: Date -> Ts -> Bond -> PriceResult
priceBond :: Date -> PlannedAmorSchedule -> Bond -> PriceResult
priceBond Date
d PlannedAmorSchedule
rc b :: Bond
b@(Bond String
_ BondType
_ OriginalInfo
_ InterestInfo
_ Maybe StepUp
_ Balance
_ Spread
_ Balance
_ Balance
_ Balance
_ Maybe Date
_ Maybe Date
_ Maybe Date
_ Maybe Statement
Nothing ) = Balance
-> Spread
-> Balance
-> Spread
-> Spread
-> Balance
-> [Txn]
-> PriceResult
PriceResult Balance
0 Spread
0 Balance
0 Spread
0 Spread
0 Balance
0 []
priceBond Date
d PlannedAmorSchedule
rc b :: Bond
b@(MultiIntBond String
_ BondType
_ OriginalInfo
_ [InterestInfo]
_ Maybe [StepUp]
_ Balance
_ [Spread]
_ Balance
_ [Balance]
_ [Balance]
_ Maybe Date
_ Maybe [Date]
_ Maybe Date
_ Maybe Statement
Nothing ) = Balance
-> Spread
-> Balance
-> Spread
-> Spread
-> Balance
-> [Txn]
-> PriceResult
PriceResult Balance
0 Spread
0 Balance
0 Spread
0 Spread
0 Balance
0 []
priceBond Date
d PlannedAmorSchedule
rc Bond
bnd
| (Balance -> Bool) -> [Balance] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Balance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0) (Txn -> Balance
S.getTxnAmt (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureCfs) = Balance
-> Spread
-> Balance
-> Spread
-> Spread
-> Balance
-> [Txn]
-> PriceResult
PriceResult Balance
0 Spread
0 Balance
0 Spread
0 Spread
0 Balance
0 []
| Bool
otherwise
= let
presentValue :: Balance
presentValue = PlannedAmorSchedule -> Date -> [Date] -> [Balance] -> Balance
pv3 PlannedAmorSchedule
rc Date
d (Txn -> Date
forall ts. TimeSeries ts => ts -> Date
getDate (Txn -> Date) -> [Txn] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureCfs) (Txn -> Balance
getTxnAmt (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureCfs)
cutoffBalance :: Balance
cutoffBalance = case [Txn] -> Date -> Maybe Txn
S.getTxnAsOf [Txn]
txns Date
d of
Maybe Txn
Nothing -> (Txn -> Balance
S.getTxnBegBalance (Txn -> Balance) -> ([Txn] -> Txn) -> [Txn] -> Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Txn] -> Txn
forall a. HasCallStack => [a] -> a
head) [Txn]
txns
Just Txn
_txn -> Txn -> Balance
S.getTxnBegBalance Txn
_txn
accruedInt :: Balance
accruedInt = Date -> Date -> [Txn] -> Balance
backoutAccruedInt Date
d (Bond -> Date
forall lb. Liable lb => lb -> Date
getOriginDate Bond
bnd) [Txn]
txns
wal :: Rational
wal = Date -> Bond -> Rational
calcWalBond Date
d Bond
bnd
duration :: Rational
duration = DayCount
-> Date -> [(Date, Balance)] -> PlannedAmorSchedule -> Rational
calcDuration DayCount
DC_ACT_365F Date
d ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
futureCfDates [Balance]
futureCfFlow) PlannedAmorSchedule
rc
convexity :: Rational
convexity = DayCount
-> Date -> [(Date, Balance)] -> PlannedAmorSchedule -> Rational
calcConvexity DayCount
DC_ACT_365F Date
d ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
futureCfDates [Balance]
futureCfFlow) PlannedAmorSchedule
rc
in
Balance
-> Spread
-> Balance
-> Spread
-> Spread
-> Balance
-> [Txn]
-> PriceResult
PriceResult Balance
presentValue (Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational (Rational
100Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Balance -> Balance -> Rational
forall a. (Eq a, Fractional a, Real a) => a -> a -> Rational
safeDivide' Balance
presentValue Balance
obal))) (Rational -> Balance
forall a b. (Real a, Fractional b) => a -> b
realToFrac Rational
wal) (Rational -> Spread
forall a b. (Real a, Fractional b) => a -> b
realToFrac Rational
duration) (Rational -> Spread
forall a b. (Real a, Fractional b) => a -> b
realToFrac Rational
convexity) Balance
accruedInt [Txn]
futureCfs
where
cr :: Spread
cr = Bond -> Spread
forall lb. Liable lb => lb -> Spread
getCurRate Bond
bnd
bal :: Balance
bal = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getCurBalance Bond
bnd
txns :: [Txn]
txns = Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns Bond
bnd
futureCfs :: [Txn]
futureCfs = CutoffType -> DateDirection -> Date -> [Txn] -> [Txn]
forall ts.
TimeSeries ts =>
CutoffType -> DateDirection -> Date -> [ts] -> [ts]
cutBy CutoffType
Exc DateDirection
Future Date
d [Txn]
txns
futureCfDates :: [Date]
futureCfDates = Txn -> Date
forall ts. TimeSeries ts => ts -> Date
getDate (Txn -> Date) -> [Txn] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureCfs
futureCfFlow :: [Balance]
futureCfFlow = Txn -> Balance
getTxnAmt (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureCfs
obal :: Balance
obal = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getOriginBalance Bond
bnd
od :: Date
od = Bond -> Date
forall lb. Liable lb => lb -> Date
getOriginDate Bond
bnd
valueBond :: BondPricingMethod -> Date -> [(Date,Balance)] -> Balance
valueBond :: BondPricingMethod -> Date -> [(Date, Balance)] -> Balance
valueBond BondPricingMethod
_ Date
_ [] = Balance
0
extractIrrResult :: PriceResult -> Maybe IRR
PriceResult
priceResult = (Spread, [Txn]) -> Spread
forall a b. (a, b) -> a
fst ((Spread, [Txn]) -> Spread)
-> Maybe (Spread, [Txn]) -> Maybe Spread
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (First (Spread, [Txn])) PriceResult (Spread, [Txn])
-> PriceResult -> Maybe (Spread, [Txn])
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First (Spread, [Txn])) PriceResult (Spread, [Txn])
Prism' PriceResult (Spread, [Txn])
_IrrResult PriceResult
priceResult
backoutAccruedInt :: Date -> Date -> [Txn] -> Amount
backoutAccruedInt :: Date -> Date -> [Txn] -> Balance
backoutAccruedInt Date
d Date
txnStartDate [Txn]
txns =
case [Txn] -> Date -> SplitType -> ([Txn], [Txn])
forall a. TimeSeries a => [a] -> Date -> SplitType -> ([a], [a])
splitByDate [Txn]
txns Date
d SplitType
EqToLeft of
([Txn]
lastTxns, []) -> Balance
0
([], Txn
x:[Txn]
xs) -> Balance -> Date -> Date -> Spread -> DayCount -> Balance
IR.calcInt (Txn -> Balance
S.getTxnBegBalance Txn
x) Date
txnStartDate Date
d (Txn -> Spread
getTxnRate Txn
x) DayCount
DC_ACT_365F
([Txn]
lastTxns, Txn
x:[Txn]
xs) -> Balance -> Date -> Date -> Spread -> DayCount -> Balance
IR.calcInt (Txn -> Balance
S.getTxnBegBalance Txn
x) (Txn -> Date
forall ts. TimeSeries ts => ts -> Date
getDate ([Txn] -> Txn
forall a. HasCallStack => [a] -> a
last [Txn]
lastTxns)) Date
d (Txn -> Spread
getTxnRate Txn
x) DayCount
DC_ACT_365F
weightAverageBalance :: Date -> Date -> Bond -> Balance
weightAverageBalance :: Date -> Date -> Bond -> Balance
weightAverageBalance Date
sd Date
ed b :: Bond
b@(Bond String
_ BondType
_ (OriginalInfo Balance
ob Date
bd Rational
_ Maybe Date
_ ) InterestInfo
_ Maybe StepUp
_ Balance
currentBalance Spread
_ Balance
_ Balance
_ Balance
_ Maybe Date
_ Maybe Date
_ Maybe Date
_ Maybe Statement
Nothing)
= Balance -> Rational -> Balance
mulBR Balance
currentBalance (DayCount -> Date -> Date -> Rational
yearCountFraction DayCount
DC_ACT_365F (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
bd Date
sd) Date
ed)
weightAverageBalance Date
sd Date
ed b :: Bond
b@(MultiIntBond String
_ BondType
_ (OriginalInfo Balance
ob Date
bd Rational
_ Maybe Date
_ ) [InterestInfo]
_ Maybe [StepUp]
_ Balance
currentBalance [Spread]
_ Balance
_ [Balance]
_ [Balance]
_ Maybe Date
_ Maybe [Date]
_ Maybe Date
_ Maybe Statement
Nothing)
= Balance -> Rational -> Balance
mulBR Balance
currentBalance (DayCount -> Date -> Date -> Rational
yearCountFraction DayCount
DC_ACT_365F (Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
bd Date
sd) Date
ed)
weightAverageBalance Date
sd Date
ed b :: Bond
b@(Bond String
_ BondType
_ (OriginalInfo Balance
ob Date
bd Rational
_ Maybe Date
_ ) InterestInfo
_ Maybe StepUp
_ Balance
currentBalance Spread
_ Balance
_ Balance
_ Balance
_ Maybe Date
_ Maybe Date
_ Maybe Date
_ (Just (S.Statement DList Txn
txns)))
= Date -> Date -> [Txn] -> Balance
S.weightAvgBalance'
(Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
bd Date
sd)
Date
ed
(DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns)
weightAverageBalance Date
sd Date
ed b :: Bond
b@(MultiIntBond String
_ BondType
_ (OriginalInfo Balance
ob Date
bd Rational
_ Maybe Date
_ ) [InterestInfo]
_ Maybe [StepUp]
_ Balance
currentBalance [Spread]
_ Balance
_ [Balance]
_ [Balance]
_ Maybe Date
_ Maybe [Date]
_ Maybe Date
_ (Just (S.Statement DList Txn
txns)))
= Date -> Date -> [Txn] -> Balance
S.weightAvgBalance'
(Date -> Date -> Date
forall a. Ord a => a -> a -> a
max Date
bd Date
sd)
Date
ed
(DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns)
weightAverageBalance Date
sd Date
ed bg :: Bond
bg@(BondGroup Map String Bond
bMap Maybe BondType
_)
= [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 -> Date -> Bond -> Balance
weightAverageBalance Date
sd Date
ed (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
tryCalcZspread :: Rational -> Balance -> Date -> [(Date,Balance)] -> Ts -> Double -> Double
tryCalcZspread :: Rational
-> Balance
-> Date
-> [(Date, Balance)]
-> PlannedAmorSchedule
-> Double
-> Double
tryCalcZspread Rational
tradePrice Balance
originBalance Date
priceDay [(Date, Balance)]
futureCfs PlannedAmorSchedule
riskFreeCurve Double
spread
= let
pvCurve :: PlannedAmorSchedule
pvCurve = PlannedAmorSchedule -> Rational -> PlannedAmorSchedule
shiftTsByAmt PlannedAmorSchedule
riskFreeCurve (Rational -> Rational
forall a. Fractional a => Rational -> a
fromRational (Double -> Rational
forall a. Real a => a -> Rational
toRational Double
spread))
pvs :: [Balance]
pvs = [ PlannedAmorSchedule -> Date -> Date -> Balance -> Balance
pv PlannedAmorSchedule
pvCurve Date
priceDay Date
_d Balance
_amt | (Date
_d, Balance
_amt) <- [(Date, Balance)]
futureCfs ]
newPrice :: Balance
newPrice = Balance
100 Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
* [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
pvs
faceVal :: Rational
faceVal = Balance -> Balance -> Rational
divideBB Balance
newPrice Balance
originBalance
in
Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational
faceVal Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- Rational
tradePrice)
calcZspread :: (Rational,Date) -> Bond -> Ts -> Either String Spread
calcZspread :: (Rational, Date)
-> Bond -> PlannedAmorSchedule -> Either String Spread
calcZspread (Rational, Date)
_ b :: Bond
b@Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} PlannedAmorSchedule
_ = String -> Either String Spread
forall a b. a -> Either a b
Left String
"No Cashflow for bond"
calcZspread (Rational, Date)
_ b :: Bond
b@MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} PlannedAmorSchedule
_ = String -> Either String Spread
forall a b. a -> Either a b
Left String
"No Cashflow for bond"
calcZspread (Rational
tradePrice,Date
priceDay) Bond
b PlannedAmorSchedule
riskFreeCurve =
let
txns :: [Txn]
txns = Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns Bond
b
bInfo :: OriginalInfo
bInfo = Bond -> OriginalInfo
bndOriginInfo Bond
b
([Txn]
_,[Txn]
futureTxns) = [Txn] -> Date -> SplitType -> ([Txn], [Txn])
forall a. TimeSeries a => [a] -> Date -> SplitType -> ([a], [a])
splitByDate [Txn]
txns Date
priceDay SplitType
EqToRight
cashflow :: [Balance]
cashflow = Txn -> Balance
S.getTxnAmt (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureTxns
ds :: [Date]
ds = Txn -> Date
forall ts. TimeSeries ts => ts -> Date
S.getDate (Txn -> Date) -> [Txn] -> [Date]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
futureTxns
oBalance :: Balance
oBalance = OriginalInfo -> Balance
originBalance OriginalInfo
bInfo
itertimes :: Int
itertimes = Int
500
def :: RiddersParam
def = RiddersParam { riddersMaxIter :: Int
riddersMaxIter = Int
itertimes, riddersTol :: Tolerance
riddersTol = Double -> Tolerance
RelTol Double
0.00001 }
in
case RiddersParam
-> (Double, Double) -> (Double -> Double) -> Root Double
ridders RiddersParam
def (Double
0.0001,Double
100) (Rational
-> Balance
-> Date
-> [(Date, Balance)]
-> PlannedAmorSchedule
-> Double
-> Double
tryCalcZspread Rational
tradePrice Balance
oBalance Date
priceDay ([Date] -> [Balance] -> [(Date, Balance)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Date]
ds [Balance]
cashflow) PlannedAmorSchedule
riskFreeCurve) of
Root Double
r -> Spread -> Either String Spread
forall a b. b -> Either a b
Right (Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational (Double -> Rational
forall a. Real a => a -> Rational
toRational Double
r))
Root Double
_ -> String -> Either String Spread
forall a b. a -> Either a b
Left (String -> Either String Spread) -> String -> Either String Spread
forall a b. (a -> b) -> a -> b
$ String
"Failed to find Z spread with "String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
itertimes String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" times try"
totalFundedBalance :: Bond -> Balance
totalFundedBalance :: Bond -> Balance
totalFundedBalance (BondGroup Map String Bond
bMap Maybe BondType
_) = [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
$ Bond -> Balance
totalFundedBalance (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
totalFundedBalance Bond
b
= let
txns :: [Txn]
txns = Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns Bond
b
isFundingTxn :: TxnComment -> Bool
isFundingTxn (FundWith String
_ Balance
_) = Bool
True
isFundingTxn TxnComment
_ = Bool
False
fundingTxns :: [Txn]
fundingTxns = (TxnComment -> Bool) -> [Txn] -> [Txn]
S.filterTxn TxnComment -> Bool
isFundingTxn [Txn]
txns
in
[Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Balance] -> Balance) -> [Balance] -> Balance
forall a b. (a -> b) -> a -> b
$ (\(BondTxn Date
d Balance
b Balance
i Balance
p Spread
r0 Balance
c Balance
di Balance
dioi Maybe Float
f TxnComment
t) -> Balance -> Balance
forall a. Num a => a -> a
abs Balance
p) (Txn -> Balance) -> [Txn] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Txn]
fundingTxns
buildRateResetDates :: Bond -> StartDate -> EndDate -> [Date]
buildRateResetDates :: Bond -> Date -> Date -> [Date]
buildRateResetDates (BondGroup Map String Bond
bMap Maybe BondType
_) Date
sd Date
ed = [[Date]] -> [Date]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Date]] -> [Date]) -> [[Date]] -> [Date]
forall a b. (a -> b) -> a -> b
$ (\Bond
x -> Bond -> Date -> Date -> [Date]
buildRateResetDates Bond
x Date
sd Date
ed) (Bond -> [Date]) -> [Bond] -> [[Date]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
buildRateResetDates b :: Bond
b@Bond{bndInterestInfo :: Bond -> InterestInfo
bndInterestInfo = InterestInfo
ii,bndStepUp :: Bond -> Maybe StepUp
bndStepUp = Maybe StepUp
mSt } Date
sd Date
ed
= let
resetDp :: Maybe RateReset
resetDp = InterestInfo -> Maybe RateReset
getDpFromIntInfo InterestInfo
ii
floaterRateResetDates :: Maybe RateReset -> [Date]
floaterRateResetDates (Just RateReset
dp) = RangeType -> Date -> RateReset -> Date -> [Date]
genSerialDatesTill2 RangeType
NO_IE Date
sd RateReset
dp Date
ed
floaterRateResetDates Maybe RateReset
Nothing = []
in
Maybe RateReset -> [Date]
floaterRateResetDates Maybe RateReset
resetDp
buildRateResetDates b :: Bond
b@MultiIntBond{bndInterestInfos :: Bond -> [InterestInfo]
bndInterestInfos = [InterestInfo]
iis} Date
sd Date
ed
= let
floaterRateResetDates :: Maybe RateReset -> [Date]
floaterRateResetDates (Just RateReset
dp) = RangeType -> Date -> RateReset -> Date -> [Date]
genSerialDatesTill2 RangeType
NO_IE Date
sd RateReset
dp Date
ed
floaterRateResetDates Maybe RateReset
Nothing = []
in
[[Date]] -> [Date]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Date]] -> [Date]) -> [[Date]] -> [Date]
forall a b. (a -> b) -> a -> b
$ (Maybe RateReset -> [Date]
floaterRateResetDates (Maybe RateReset -> [Date])
-> (InterestInfo -> Maybe RateReset) -> InterestInfo -> [Date]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterestInfo -> Maybe RateReset
getDpFromIntInfo) (InterestInfo -> [Date]) -> [InterestInfo] -> [[Date]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [InterestInfo]
iis
buildStepUpDates :: Bond -> StartDate -> EndDate -> [Date]
buildStepUpDates :: Bond -> Date -> Date -> [Date]
buildStepUpDates (BondGroup Map String Bond
bMap Maybe BondType
_) Date
sd Date
ed = [[Date]] -> [Date]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Date]] -> [Date]) -> [[Date]] -> [Date]
forall a b. (a -> b) -> a -> b
$ (\Bond
x -> Bond -> Date -> Date -> [Date]
buildStepUpDates Bond
x Date
sd Date
ed) (Bond -> [Date]) -> [Bond] -> [[Date]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
buildStepUpDates b :: Bond
b@Bond{bndStepUp :: Bond -> Maybe StepUp
bndStepUp = Maybe StepUp
mSt } Date
sd Date
ed
= case Maybe StepUp
mSt of
Maybe StepUp
Nothing -> []
Just (PassDateSpread Date
d Spread
_) -> [Date
d]
Just (PassDateLadderSpread Date
fstSd Spread
_ RateReset
dp) -> RangeType -> Date -> RateReset -> Date -> [Date]
genSerialDatesTill2 RangeType
IE Date
fstSd RateReset
dp Date
ed
buildStepUpDates b :: Bond
b@MultiIntBond{bndStepUps :: Bond -> Maybe [StepUp]
bndStepUps = Maybe [StepUp]
mSt } Date
sd Date
ed
= case Maybe [StepUp]
mSt of
Maybe [StepUp]
Nothing -> []
Just [StepUp]
sts -> Set Date -> [Date]
forall a. Set a -> [a]
Set.toList (Set Date -> [Date]) -> Set Date -> [Date]
forall a b. (a -> b) -> a -> b
$
[Date] -> Set Date
forall a. Ord a => [a] -> Set a
Set.fromList ([Date] -> Set Date) -> [Date] -> Set Date
forall a b. (a -> b) -> a -> b
$
[[Date]] -> [Date]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Date]] -> [Date]) -> [[Date]] -> [Date]
forall a b. (a -> b) -> a -> b
$
(\StepUp
y ->
case StepUp
y of
(PassDateLadderSpread Date
fstSd Spread
_ RateReset
dp) -> RangeType -> Date -> RateReset -> Date -> [Date]
genSerialDatesTill2 RangeType
IE Date
fstSd RateReset
dp Date
ed
(PassDateSpread Date
d Spread
_) -> [Date
d]
) (StepUp -> [Date]) -> [StepUp] -> [[Date]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [StepUp]
sts
instance S.QueryByComment Bond where
queryStmt :: Bond -> TxnComment -> [Txn]
queryStmt Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} TxnComment
tc = []
queryStmt MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} TxnComment
tc = []
queryStmt Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Just (S.Statement DList Txn
txns)} TxnComment
tc
= (Txn -> Bool) -> [Txn] -> [Txn]
forall a. (a -> Bool) -> [a] -> [a]
Data.List.filter (\Txn
x -> Txn -> TxnComment
S.getTxnComment Txn
x TxnComment -> TxnComment -> Bool
forall a. Eq a => a -> a -> Bool
== TxnComment
tc) (DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns)
queryStmt MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Just (S.Statement DList Txn
txns)} TxnComment
tc
= (Txn -> Bool) -> [Txn] -> [Txn]
forall a. (a -> Bool) -> [a] -> [a]
Data.List.filter (\Txn
x -> Txn -> TxnComment
S.getTxnComment Txn
x TxnComment -> TxnComment -> Bool
forall a. Eq a => a -> a -> Bool
== TxnComment
tc) (DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns)
instance Liable Bond where
isPaidOff :: Bond -> Bool
isPaidOff b :: Bond
b@Bond{bndBalance :: Bond -> Balance
bndBalance=Balance
bal, bndDueInt :: Bond -> Balance
bndDueInt=Balance
di, bndDueIntOverInt :: Bond -> Balance
bndDueIntOverInt=Balance
dioi}
| Balance
balBalance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0 Bool -> Bool -> Bool
&& Balance
diBalance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0 Bool -> Bool -> Bool
&& Balance
dioiBalance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0 = Bool
True
| Bool
otherwise = Bool
False
isPaidOff MultiIntBond{bndBalance :: Bond -> Balance
bndBalance=Balance
bal, bndDueInts :: Bond -> [Balance]
bndDueInts=[Balance]
dis, bndDueIntOverInts :: Bond -> [Balance]
bndDueIntOverInts=[Balance]
diois}
| Balance
balBalance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0 Bool -> Bool -> Bool
&& [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
disBalance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0 Bool -> Bool -> Bool
&& [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
dioisBalance -> Balance -> Bool
forall a. Eq a => a -> a -> Bool
==Balance
0 = Bool
True
| Bool
otherwise = Bool
False
isPaidOff (BondGroup Map String Bond
bMap Maybe BondType
_) = (Bool -> Bool) -> [Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
==Bool
True) ([Bool] -> Bool) -> [Bool] -> Bool
forall a b. (a -> b) -> a -> b
$ Bond -> Bool
forall lb. Liable lb => lb -> Bool
isPaidOff (Bond -> Bool) -> [Bond] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getCurBalance :: Bond -> Balance
getCurBalance b :: Bond
b@Bond {bndBalance :: Bond -> Balance
bndBalance = Balance
bal } = Balance
bal
getCurBalance b :: Bond
b@MultiIntBond {bndBalance :: Bond -> Balance
bndBalance = Balance
bal } = Balance
bal
getCurBalance (BondGroup Map String Bond
bMap Maybe BondType
_) = [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
$ Bond -> Balance
forall lb. Liable lb => lb -> Balance
getCurBalance (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getCurRate :: Bond -> Spread
getCurRate Bond{bndRate :: Bond -> Spread
bndRate = Spread
r} = Spread
r
getCurRate MultiIntBond{bndRates :: Bond -> [Spread]
bndRates = [Spread]
rs} = [Spread] -> Spread
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Spread]
rs
getCurRate (BondGroup Map String Bond
bMap Maybe BondType
_) =
Rational -> Spread
forall a. Fractional a => Rational -> a
fromRational (Rational -> Spread) -> Rational -> Spread
forall a b. (a -> b) -> a -> b
$
[Rational] -> [Rational] -> Rational
weightedBy
(Balance -> Rational
forall a. Real a => a -> Rational
toRational (Balance -> Rational) -> (Bond -> Balance) -> Bond -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bond -> Balance
forall lb. Liable lb => lb -> Balance
getCurBalance (Bond -> Rational) -> [Bond] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap)
(Spread -> Rational
forall a. Real a => a -> Rational
toRational (Spread -> Rational) -> (Bond -> Spread) -> Bond -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bond -> Spread
forall lb. Liable lb => lb -> Spread
getCurRate (Bond -> Rational) -> [Bond] -> [Rational]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap)
getOriginBalance :: Bond -> Balance
getOriginBalance (BondGroup Map String Bond
bMap Maybe BondType
_) = [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
$ Bond -> Balance
forall lb. Liable lb => lb -> Balance
getOriginBalance (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getOriginBalance Bond
b = OriginalInfo -> Balance
originBalance (OriginalInfo -> Balance) -> OriginalInfo -> Balance
forall a b. (a -> b) -> a -> b
$ Bond -> OriginalInfo
bndOriginInfo Bond
b
getOriginDate :: Bond -> Date
getOriginDate Bond
b = OriginalInfo -> Date
originDate (OriginalInfo -> Date) -> OriginalInfo -> Date
forall a b. (a -> b) -> a -> b
$ Bond -> OriginalInfo
bndOriginInfo Bond
b
getAccrueBegDate :: Bond -> Date
getAccrueBegDate Bond
b = case Bond -> Maybe Date
bndDueIntDate Bond
b of
Just Date
d -> Date
d
Maybe Date
Nothing -> Bond -> Date
forall lb. Liable lb => lb -> Date
getOriginDate Bond
b
getDueInt :: Bond -> Balance
getDueInt b :: Bond
b@Bond{bndDueInt :: Bond -> Balance
bndDueInt=Balance
di} = Balance
di
getDueInt MultiIntBond{bndDueInts :: Bond -> [Balance]
bndDueInts=[Balance]
dis} = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
dis
getDueInt (BondGroup Map String Bond
bMap Maybe BondType
_) = [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
$ Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueInt (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getDueIntAt :: Bond -> Int -> Balance
getDueIntAt MultiIntBond{bndDueInts :: Bond -> [Balance]
bndDueInts=[Balance]
dis} Int
idx = [Balance]
dis [Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!! Int
idx
getDueIntOverIntAt :: Bond -> Int -> Balance
getDueIntOverIntAt MultiIntBond{bndDueIntOverInts :: Bond -> [Balance]
bndDueIntOverInts=[Balance]
diois} Int
idx = [Balance]
diois [Balance] -> Int -> Balance
forall a. HasCallStack => [a] -> Int -> a
!! Int
idx
getTotalDueIntAt :: Bond -> Int -> Balance
getTotalDueIntAt Bond
b Int
idx = Bond -> Int -> Balance
forall lb. Liable lb => lb -> Int -> Balance
getDueIntAt Bond
b Int
idx Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Bond -> Int -> Balance
forall lb. Liable lb => lb -> Int -> Balance
getDueIntOverIntAt Bond
b Int
idx
getDueIntOverInt :: Bond -> Balance
getDueIntOverInt b :: Bond
b@Bond{bndDueIntOverInt :: Bond -> Balance
bndDueIntOverInt=Balance
dioi} = Balance
dioi
getDueIntOverInt MultiIntBond{bndDueIntOverInts :: Bond -> [Balance]
bndDueIntOverInts=[Balance]
diois} = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
diois
getDueIntOverInt (BondGroup Map String Bond
bMap Maybe BondType
_) = [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
$ Bond -> Balance
forall lb. Liable lb => lb -> Balance
getDueIntOverInt (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getTotalDueInt :: Bond -> Balance
getTotalDueInt b :: Bond
b@Bond{bndDueInt :: Bond -> Balance
bndDueInt=Balance
di,bndDueIntOverInt :: Bond -> Balance
bndDueIntOverInt=Balance
dioi} = Balance
di Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
dioi
getTotalDueInt MultiIntBond{bndDueInts :: Bond -> [Balance]
bndDueInts=[Balance]
dis,bndDueIntOverInts :: Bond -> [Balance]
bndDueIntOverInts=[Balance]
diois} = [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
dis Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ [Balance] -> Balance
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Balance]
diois
getTotalDueInt (BondGroup Map String Bond
bMap Maybe BondType
_ ) = [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
$ Bond -> Balance
forall lb. Liable lb => lb -> Balance
getTotalDueInt (Bond -> Balance) -> [Bond] -> [Balance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getOutstandingAmount :: Bond -> Balance
getOutstandingAmount Bond
b = Bond -> Balance
forall lb. Liable lb => lb -> Balance
getTotalDueInt Bond
b Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Bond -> Balance
forall lb. Liable lb => lb -> Balance
getCurBalance Bond
b
instance IR.UseRate Bond where
isAdjustbleRate :: Bond -> Bool
isAdjustbleRate :: Bond -> Bool
isAdjustbleRate Bond{bndInterestInfo :: Bond -> InterestInfo
bndInterestInfo = InterestInfo
iinfo} = InterestInfo -> Bool
isAdjustble InterestInfo
iinfo
getIndexes :: Bond -> Maybe [Index]
getIndexes Bond{bndInterestInfo :: Bond -> InterestInfo
bndInterestInfo = InterestInfo
iinfo} = InterestInfo -> Maybe [Index]
getIndexFromInfo InterestInfo
iinfo
getIndexes (BondGroup Map String Bond
bMap Maybe BondType
_) = if [Index] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Data.List.null [Index]
combined then Maybe [Index]
forall a. Maybe a
Nothing else [Index] -> Maybe [Index]
forall a. a -> Maybe a
Just [Index]
combined
where combined :: [Index]
combined = [[Index]] -> [Index]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Index]] -> [Index])
-> ([Maybe [Index]] -> [[Index]]) -> [Maybe [Index]] -> [Index]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe [Index]] -> [[Index]]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe [Index]] -> [Index]) -> [Maybe [Index]] -> [Index]
forall a b. (a -> b) -> a -> b
$ (\Bond
b -> InterestInfo -> Maybe [Index]
getIndexFromInfo (Bond -> InterestInfo
bndInterestInfo Bond
b)) (Bond -> Maybe [Index]) -> [Bond] -> [Maybe [Index]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
getIndexes MultiIntBond{bndInterestInfos :: Bond -> [InterestInfo]
bndInterestInfos = [InterestInfo]
iis}
= [Index] -> Maybe [Index]
forall a. a -> Maybe a
Just ([Index] -> Maybe [Index]) -> [Index] -> Maybe [Index]
forall a b. (a -> b) -> a -> b
$ [[Index]] -> [Index]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Index]] -> [Index]) -> [[Index]] -> [Index]
forall a b. (a -> b) -> a -> b
$ Maybe [Index] -> [Index]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Maybe [Index] -> [Index])
-> (InterestInfo -> Maybe [Index]) -> InterestInfo -> [Index]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InterestInfo -> Maybe [Index]
getIndexFromInfo (InterestInfo -> [Index]) -> [InterestInfo] -> [[Index]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [InterestInfo]
iis
instance S.HasStmt Bond where
getAllTxns :: Bond -> [Txn]
getAllTxns Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} = []
getAllTxns Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Just (S.Statement DList Txn
txns)} = DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns
getAllTxns MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} = []
getAllTxns MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Just (S.Statement DList Txn
txns)} = DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns
getAllTxns (BondGroup Map String Bond
bMap Maybe BondType
_) = [[Txn]] -> [Txn]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Txn]] -> [Txn]) -> [[Txn]] -> [Txn]
forall a b. (a -> b) -> a -> b
$ Bond -> [Txn]
forall a. HasStmt a => a -> [Txn]
S.getAllTxns (Bond -> [Txn]) -> [Bond] -> [[Txn]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
hasEmptyTxn :: Bond -> Bool
hasEmptyTxn Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} = Bool
True
hasEmptyTxn Bond{bndStmt :: Bond -> Maybe Statement
bndStmt = Just (S.Statement DList Txn
txn)} = DList Txn
txn DList Txn -> DList Txn -> Bool
forall a. Eq a => a -> a -> Bool
== DList Txn
forall a. DList a
DL.empty
hasEmptyTxn MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Maybe Statement
Nothing} = Bool
True
hasEmptyTxn MultiIntBond{bndStmt :: Bond -> Maybe Statement
bndStmt = Just (S.Statement DList Txn
txn)} = DList Txn
txn DList Txn -> DList Txn -> Bool
forall a. Eq a => a -> a -> Bool
== DList Txn
forall a. DList a
DL.empty
hasEmptyTxn (BondGroup Map String Bond
bMap Maybe BondType
_) = (Bond -> Bool) -> [Bond] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Bond -> Bool
forall a. HasStmt a => a -> Bool
S.hasEmptyTxn ([Bond] -> Bool) -> [Bond] -> Bool
forall a b. (a -> b) -> a -> b
$ Map String Bond -> [Bond]
forall k a. Map k a -> [a]
Map.elems Map String Bond
bMap
hasEmptyTxn Bond
_ = Bool
False
makeLensesFor [("bndType","bndTypeLens"),("bndOriginInfo","bndOriginInfoLens"),("bndInterestInfo","bndIntLens"),("bndStmt","bndStmtLens")] ''Bond
makeLensesFor [("bndOriginDate","bndOriginDateLens"),("bndOriginBalance","bndOriginBalanceLens"),("bndOriginRate","bndOriginRateLens")] ''OriginalInfo
makePrisms ''Bond
$(deriveJSON defaultOptions ''InterestOverInterestType)
$(deriveJSON defaultOptions ''InterestInfo)
$(deriveJSON defaultOptions ''OriginalInfo)
$(deriveJSON defaultOptions ''BondType)
$(deriveJSON defaultOptions ''StepUp)
$(deriveJSON defaultOptions ''Bond)