{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables #-}
module AssetClass.MixedAsset
(projAssetUnion,projAssetUnionList,projectCashflow, calcAssetUnion,curBal)
where
import qualified Data.Time as T
import qualified Cashflow as CF
import qualified Assumptions as A
import qualified AssetClass.AssetBase as ACM
import InterestRate
import qualified Asset as P
import Lib
import Util
import DateUtil
import Types
import qualified Data.Map as Map
import Data.List
import Data.Maybe
import Data.Aeson hiding (json)
import Language.Haskell.TH
import Data.Aeson.TH
import Data.Aeson.Types
import GHC.Generics
import AssetClass.AssetBase
import AssetClass.Mortgage
import AssetClass.Lease
import AssetClass.Loan
import AssetClass.Installment
import AssetClass.Receivable
import AssetClass.AssetCashflow
import AssetClass.FixedAsset
import AssetClass.ProjectedCashFlow
import Debug.Trace
import Assumptions (AssetDefaultAssumption(DefaultCDR))
import qualified Asset as Ast
instance P.Asset AssetUnion where
calcCashflow :: AssetUnion
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
calcCashflow AssetUnion
ma Date
asOfDay Maybe [RateAssumption]
mRates = AssetUnion
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
calcAssetUnion AssetUnion
ma Date
asOfDay Maybe [RateAssumption]
mRates
getCurrentBal :: AssetUnion -> BeginBalance
getCurrentBal AssetUnion
ma = AssetUnion -> BeginBalance
curBal AssetUnion
ma
getOriginBal :: AssetUnion -> BeginBalance
getOriginBal AssetUnion
ma = AssetUnion -> BeginBalance
origBal AssetUnion
ma
getOriginRate :: AssetUnion -> IRate
getOriginRate AssetUnion
ma = AssetUnion -> IRate
origRate AssetUnion
ma
getCurrentRate :: AssetUnion -> IRate
getCurrentRate AssetUnion
ma = AssetUnion -> IRate
currRate AssetUnion
ma
getOriginDate :: AssetUnion -> Date
getOriginDate AssetUnion
ma = AssetUnion -> Date
origDate AssetUnion
ma
getOriginInfo :: AssetUnion -> OriginalInfo
getOriginInfo AssetUnion
ma = AssetUnion -> OriginalInfo
origInfo AssetUnion
ma
isDefaulted :: AssetUnion -> Bool
isDefaulted = AssetUnion -> Bool
isDefault
getPaymentDates :: AssetUnion -> Int -> [Date]
getPaymentDates AssetUnion
ma Int
n = AssetUnion -> Int -> [Date]
getPaydates AssetUnion
ma Int
n
getRemainTerms :: AssetUnion -> Int
getRemainTerms = AssetUnion -> Int
remainTerms
projCashflow :: AssetUnion
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
projCashflow AssetUnion
ma Date
asOfDay AssetPerf
assumps Maybe [RateAssumption]
mRates = AssetUnion
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
projAssetUnion AssetUnion
ma Date
asOfDay AssetPerf
assumps Maybe [RateAssumption]
mRates
getBorrowerNum :: AssetUnion -> Int
getBorrowerNum = AssetUnion -> Int
borrowerNum
splitWith :: AssetUnion -> [Rate] -> [AssetUnion]
splitWith = AssetUnion -> [Rate] -> [AssetUnion]
splitWith
updateOriginDate :: AssetUnion -> Date -> AssetUnion
updateOriginDate = AssetUnion -> Date -> AssetUnion
updateOrigDate
calcAlignDate :: AssetUnion -> Date -> Date
calcAlignDate = AssetUnion -> Date -> Date
calcAlignDate
curBal:: ACM.AssetUnion -> Balance
curBal :: AssetUnion -> BeginBalance
curBal (ACM.MO Mortgage
ast) = Mortgage -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal Mortgage
ast
curBal (ACM.LO Loan
ast) = Loan -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal Loan
ast
curBal (ACM.IL Installment
ast) = Installment -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal Installment
ast
curBal (ACM.LS Lease
ast) = Lease -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal Lease
ast
curBal (ACM.FA FixedAsset
ast) = FixedAsset -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal FixedAsset
ast
curBal (ACM.RE Receivable
ast) = Receivable -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal Receivable
ast
curBal (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getCurrentBal ProjectedCashflow
ast
origBal :: ACM.AssetUnion -> Balance
origBal :: AssetUnion -> BeginBalance
origBal (ACM.MO Mortgage
ast) = Mortgage -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal Mortgage
ast
origBal (ACM.LO Loan
ast) = Loan -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal Loan
ast
origBal (ACM.IL Installment
ast) = Installment -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal Installment
ast
origBal (ACM.LS Lease
ast) = Lease -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal Lease
ast
origBal (ACM.FA FixedAsset
ast) = FixedAsset -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal FixedAsset
ast
origBal (ACM.RE Receivable
ast) = Receivable -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal Receivable
ast
origBal (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> BeginBalance
forall a. Asset a => a -> BeginBalance
P.getOriginBal ProjectedCashflow
ast
origRate :: ACM.AssetUnion -> IRate
origRate :: AssetUnion -> IRate
origRate (ACM.MO Mortgage
ast) = Mortgage -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate Mortgage
ast
origRate (ACM.LO Loan
ast) = Loan -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate Loan
ast
origRate (ACM.IL Installment
ast) = Installment -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate Installment
ast
origRate (ACM.LS Lease
ast) = Lease -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate Lease
ast
origRate (ACM.FA FixedAsset
ast) = FixedAsset -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate FixedAsset
ast
origRate (ACM.RE Receivable
ast) = Receivable -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate Receivable
ast
origRate (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> IRate
forall a. Asset a => a -> IRate
P.getOriginRate ProjectedCashflow
ast
currRate :: ACM.AssetUnion -> IRate
currRate :: AssetUnion -> IRate
currRate (ACM.MO Mortgage
ast) = Mortgage -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate Mortgage
ast
currRate (ACM.LO Loan
ast) = Loan -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate Loan
ast
currRate (ACM.IL Installment
ast) = Installment -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate Installment
ast
currRate (ACM.LS Lease
ast) = Lease -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate Lease
ast
currRate (ACM.FA FixedAsset
ast) = FixedAsset -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate FixedAsset
ast
currRate (ACM.RE Receivable
ast) = Receivable -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate Receivable
ast
currRate (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> IRate
forall a. Asset a => a -> IRate
P.getCurrentRate ProjectedCashflow
ast
origDate :: ACM.AssetUnion -> Date
origDate :: AssetUnion -> Date
origDate (ACM.MO Mortgage
ast) = Mortgage -> Date
forall a. Asset a => a -> Date
P.getOriginDate Mortgage
ast
origDate (ACM.LO Loan
ast) = Loan -> Date
forall a. Asset a => a -> Date
P.getOriginDate Loan
ast
origDate (ACM.IL Installment
ast) = Installment -> Date
forall a. Asset a => a -> Date
P.getOriginDate Installment
ast
origDate (ACM.LS Lease
ast) = Lease -> Date
forall a. Asset a => a -> Date
P.getOriginDate Lease
ast
origDate (ACM.FA FixedAsset
ast) = FixedAsset -> Date
forall a. Asset a => a -> Date
P.getOriginDate FixedAsset
ast
origDate (ACM.RE Receivable
ast) = Receivable -> Date
forall a. Asset a => a -> Date
P.getOriginDate Receivable
ast
origDate (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> Date
forall a. Asset a => a -> Date
P.getOriginDate ProjectedCashflow
ast
origInfo :: ACM.AssetUnion -> OriginalInfo
origInfo :: AssetUnion -> OriginalInfo
origInfo (ACM.MO Mortgage
ast) = Mortgage -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo Mortgage
ast
origInfo (ACM.LO Loan
ast) = Loan -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo Loan
ast
origInfo (ACM.IL Installment
ast) = Installment -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo Installment
ast
origInfo (ACM.LS Lease
ast) = Lease -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo Lease
ast
origInfo (ACM.FA FixedAsset
ast) = FixedAsset -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo FixedAsset
ast
origInfo (ACM.RE Receivable
ast) = Receivable -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo Receivable
ast
origInfo (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> OriginalInfo
forall a. Asset a => a -> OriginalInfo
P.getOriginInfo ProjectedCashflow
ast
isDefault :: ACM.AssetUnion -> Bool
isDefault :: AssetUnion -> Bool
isDefault (ACM.MO Mortgage
ast) = Mortgage -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted Mortgage
ast
isDefault (ACM.LO Loan
ast) = Loan -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted Loan
ast
isDefault (ACM.IL Installment
ast) = Installment -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted Installment
ast
isDefault (ACM.LS Lease
ast) = Lease -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted Lease
ast
isDefault (ACM.FA FixedAsset
ast) = FixedAsset -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted FixedAsset
ast
isDefault (ACM.RE Receivable
ast) = Receivable -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted Receivable
ast
isDefault (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> Bool
forall a. Asset a => a -> Bool
P.isDefaulted ProjectedCashflow
ast
getPaydates :: ACM.AssetUnion -> Int -> [Date]
getPaydates :: AssetUnion -> Int -> [Date]
getPaydates (ACM.MO Mortgage
ast) Int
n = Mortgage -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates Mortgage
ast Int
n
getPaydates (ACM.LO Loan
ast) Int
n = Loan -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates Loan
ast Int
n
getPaydates (ACM.IL Installment
ast) Int
n = Installment -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates Installment
ast Int
n
getPaydates (ACM.LS Lease
ast) Int
n = Lease -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates Lease
ast Int
n
getPaydates (ACM.FA FixedAsset
ast) Int
n = FixedAsset -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates FixedAsset
ast Int
n
getPaydates (ACM.RE Receivable
ast) Int
n = Receivable -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates Receivable
ast Int
n
getPaydates (ACM.PF ProjectedCashflow
ast) Int
n = ProjectedCashflow -> Int -> [Date]
forall a. Asset a => a -> Int -> [Date]
P.getPaymentDates ProjectedCashflow
ast Int
n
remainTerms :: ACM.AssetUnion -> Int
remainTerms :: AssetUnion -> Int
remainTerms (ACM.MO Mortgage
ast) = Mortgage -> Int
forall a. Asset a => a -> Int
P.getRemainTerms Mortgage
ast
remainTerms (ACM.LO Loan
ast) = Loan -> Int
forall a. Asset a => a -> Int
P.getRemainTerms Loan
ast
remainTerms (ACM.IL Installment
ast) = Installment -> Int
forall a. Asset a => a -> Int
P.getRemainTerms Installment
ast
remainTerms (ACM.LS Lease
ast) = Lease -> Int
forall a. Asset a => a -> Int
P.getRemainTerms Lease
ast
remainTerms (ACM.FA FixedAsset
ast) = FixedAsset -> Int
forall a. Asset a => a -> Int
P.getRemainTerms FixedAsset
ast
remainTerms (ACM.RE Receivable
ast) = Receivable -> Int
forall a. Asset a => a -> Int
P.getRemainTerms Receivable
ast
remainTerms (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> Int
forall a. Asset a => a -> Int
P.getRemainTerms ProjectedCashflow
ast
borrowerNum :: ACM.AssetUnion -> Int
borrowerNum :: AssetUnion -> Int
borrowerNum (ACM.MO Mortgage
ast) = Mortgage -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum Mortgage
ast
borrowerNum (ACM.LO Loan
ast) = Loan -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum Loan
ast
borrowerNum (ACM.IL Installment
ast) = Installment -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum Installment
ast
borrowerNum (ACM.LS Lease
ast) = Lease -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum Lease
ast
borrowerNum (ACM.FA FixedAsset
ast) = FixedAsset -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum FixedAsset
ast
borrowerNum (ACM.RE Receivable
ast) = Receivable -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum Receivable
ast
borrowerNum (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> Int
forall a. Asset a => a -> Int
P.getBorrowerNum ProjectedCashflow
ast
splitWith :: ACM.AssetUnion -> [Rate] -> [ACM.AssetUnion]
splitWith :: AssetUnion -> [Rate] -> [AssetUnion]
splitWith (ACM.MO Mortgage
ast) [Rate]
rs = Mortgage -> AssetUnion
ACM.MO (Mortgage -> AssetUnion) -> [Mortgage] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mortgage -> [Rate] -> [Mortgage]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith Mortgage
ast [Rate]
rs
splitWith (ACM.LO Loan
ast) [Rate]
rs = Loan -> AssetUnion
ACM.LO (Loan -> AssetUnion) -> [Loan] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Loan -> [Rate] -> [Loan]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith Loan
ast [Rate]
rs
splitWith (ACM.IL Installment
ast) [Rate]
rs = Installment -> AssetUnion
ACM.IL (Installment -> AssetUnion) -> [Installment] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Installment -> [Rate] -> [Installment]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith Installment
ast [Rate]
rs
splitWith (ACM.LS Lease
ast) [Rate]
rs = Lease -> AssetUnion
ACM.LS (Lease -> AssetUnion) -> [Lease] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Lease -> [Rate] -> [Lease]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith Lease
ast [Rate]
rs
splitWith (ACM.FA FixedAsset
ast) [Rate]
rs = FixedAsset -> AssetUnion
ACM.FA (FixedAsset -> AssetUnion) -> [FixedAsset] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FixedAsset -> [Rate] -> [FixedAsset]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith FixedAsset
ast [Rate]
rs
splitWith (ACM.RE Receivable
ast) [Rate]
rs = Receivable -> AssetUnion
ACM.RE (Receivable -> AssetUnion) -> [Receivable] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Receivable -> [Rate] -> [Receivable]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith Receivable
ast [Rate]
rs
splitWith (ACM.PF ProjectedCashflow
ast) [Rate]
rs = ProjectedCashflow -> AssetUnion
ACM.PF (ProjectedCashflow -> AssetUnion)
-> [ProjectedCashflow] -> [AssetUnion]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProjectedCashflow -> [Rate] -> [ProjectedCashflow]
forall a. Asset a => a -> [Rate] -> [a]
P.splitWith ProjectedCashflow
ast [Rate]
rs
updateOrigDate :: ACM.AssetUnion -> Date -> ACM.AssetUnion
updateOrigDate :: AssetUnion -> Date -> AssetUnion
updateOrigDate (ACM.MO Mortgage
ast) Date
d = Mortgage -> AssetUnion
ACM.MO (Mortgage -> AssetUnion) -> Mortgage -> AssetUnion
forall a b. (a -> b) -> a -> b
$ Mortgage -> Date -> Mortgage
forall a. Asset a => a -> Date -> a
P.updateOriginDate Mortgage
ast Date
d
updateOrigDate (ACM.LO Loan
ast) Date
d = Loan -> AssetUnion
ACM.LO (Loan -> AssetUnion) -> Loan -> AssetUnion
forall a b. (a -> b) -> a -> b
$ Loan -> Date -> Loan
forall a. Asset a => a -> Date -> a
P.updateOriginDate Loan
ast Date
d
updateOrigDate (ACM.IL Installment
ast) Date
d = Installment -> AssetUnion
ACM.IL (Installment -> AssetUnion) -> Installment -> AssetUnion
forall a b. (a -> b) -> a -> b
$ Installment -> Date -> Installment
forall a. Asset a => a -> Date -> a
P.updateOriginDate Installment
ast Date
d
updateOrigDate (ACM.LS Lease
ast) Date
d = Lease -> AssetUnion
ACM.LS (Lease -> AssetUnion) -> Lease -> AssetUnion
forall a b. (a -> b) -> a -> b
$ Lease -> Date -> Lease
forall a. Asset a => a -> Date -> a
P.updateOriginDate Lease
ast Date
d
updateOrigDate (ACM.FA FixedAsset
ast) Date
d = FixedAsset -> AssetUnion
ACM.FA (FixedAsset -> AssetUnion) -> FixedAsset -> AssetUnion
forall a b. (a -> b) -> a -> b
$ FixedAsset -> Date -> FixedAsset
forall a. Asset a => a -> Date -> a
P.updateOriginDate FixedAsset
ast Date
d
updateOrigDate (ACM.RE Receivable
ast) Date
d = Receivable -> AssetUnion
ACM.RE (Receivable -> AssetUnion) -> Receivable -> AssetUnion
forall a b. (a -> b) -> a -> b
$ Receivable -> Date -> Receivable
forall a. Asset a => a -> Date -> a
P.updateOriginDate Receivable
ast Date
d
updateOrigDate (ACM.PF ProjectedCashflow
ast) Date
d = ProjectedCashflow -> AssetUnion
ACM.PF (ProjectedCashflow -> AssetUnion)
-> ProjectedCashflow -> AssetUnion
forall a b. (a -> b) -> a -> b
$ ProjectedCashflow -> Date -> ProjectedCashflow
forall a. Asset a => a -> Date -> a
P.updateOriginDate ProjectedCashflow
ast Date
d
calcAlignDate :: ACM.AssetUnion -> Date -> Date
calcAlignDate :: AssetUnion -> Date -> Date
calcAlignDate (ACM.MO Mortgage
ast) = Mortgage -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate Mortgage
ast
calcAlignDate (ACM.LO Loan
ast) = Loan -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate Loan
ast
calcAlignDate (ACM.IL Installment
ast) = Installment -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate Installment
ast
calcAlignDate (ACM.LS Lease
ast) = Lease -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate Lease
ast
calcAlignDate (ACM.FA FixedAsset
ast) = FixedAsset -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate FixedAsset
ast
calcAlignDate (ACM.RE Receivable
ast) = Receivable -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate Receivable
ast
calcAlignDate (ACM.PF ProjectedCashflow
ast) = ProjectedCashflow -> Date -> Date
forall a. Asset a => a -> Date -> Date
P.calcAlignDate ProjectedCashflow
ast
calcAssetUnion :: ACM.AssetUnion -> Date -> Maybe [RateAssumption] -> Either String CF.CashFlowFrame
calcAssetUnion :: AssetUnion
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
calcAssetUnion (ACM.MO Mortgage
ast) Date
d Maybe [RateAssumption]
mRates = Mortgage
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow Mortgage
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion (ACM.LO Loan
ast) Date
d Maybe [RateAssumption]
mRates = Loan
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow Loan
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion (ACM.IL Installment
ast) Date
d Maybe [RateAssumption]
mRates = Installment
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow Installment
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion (ACM.LS Lease
ast) Date
d Maybe [RateAssumption]
mRates = Lease
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow Lease
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion (ACM.FA FixedAsset
ast) Date
d Maybe [RateAssumption]
mRates = FixedAsset
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow FixedAsset
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion (ACM.RE Receivable
ast) Date
d Maybe [RateAssumption]
mRates = Receivable
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow Receivable
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion (ACM.PF ProjectedCashflow
ast) Date
d Maybe [RateAssumption]
mRates = ProjectedCashflow
-> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
forall a.
Asset a =>
a -> Date -> Maybe [RateAssumption] -> Either [Char] CashFlowFrame
P.calcCashflow ProjectedCashflow
ast Date
d Maybe [RateAssumption]
mRates
calcAssetUnion AssetUnion
x Date
_ Maybe [RateAssumption]
_ = [Char] -> Either [Char] CashFlowFrame
forall a b. a -> Either a b
Left ([Char]
"Failed to match proj AssetUnion"[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ AssetUnion -> [Char]
forall a. Show a => a -> [Char]
show AssetUnion
x)
projAssetUnion :: ACM.AssetUnion -> Date -> A.AssetPerf -> Maybe [RateAssumption]
-> Either String (CF.CashFlowFrame, Map.Map CutoffFields Balance)
projAssetUnion :: AssetUnion
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
projAssetUnion (ACM.MO Mortgage
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = Mortgage
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow Mortgage
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion (ACM.LO Loan
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = Loan
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow Loan
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion (ACM.IL Installment
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = Installment
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow Installment
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion (ACM.LS Lease
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = Lease
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow Lease
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion (ACM.FA FixedAsset
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = FixedAsset
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow FixedAsset
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion (ACM.RE Receivable
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = Receivable
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow Receivable
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion (ACM.PF ProjectedCashflow
ast) Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates = ProjectedCashflow
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a.
Asset a =>
a
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
P.projCashflow ProjectedCashflow
ast Date
d AssetPerf
assumps Maybe [RateAssumption]
mRates
projAssetUnion AssetUnion
x Date
_ AssetPerf
_ Maybe [RateAssumption]
_ = [Char]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a b. a -> Either a b
Left ([Char]
"Failed to match proj AssetUnion"[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ AssetUnion -> [Char]
forall a. Show a => a -> [Char]
show AssetUnion
x)
projAssetUnionList :: [ACM.AssetUnion] -> Date -> A.ApplyAssumptionType -> Maybe [RateAssumption]
-> Either String (CF.CashFlowFrame, Map.Map CutoffFields Balance)
projAssetUnionList :: [AssetUnion]
-> Date
-> ApplyAssumptionType
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
projAssetUnionList [] Date
d (A.PoolLevel AssetPerf
assetPerf) Maybe [RateAssumption]
mRate = (CashFlowFrame, Map CutoffFields BeginBalance)
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a b. b -> Either a b
Right ((CashFlowFrame, Map CutoffFields BeginBalance)
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
-> (CashFlowFrame, Map CutoffFields BeginBalance)
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a b. (a -> b) -> a -> b
$ (BeginStatus -> [TsRow] -> CashFlowFrame
CF.CashFlowFrame (BeginBalance
0,Date
d,Maybe BeginBalance
forall a. Maybe a
Nothing) [], Map CutoffFields BeginBalance
forall k a. Map k a
Map.empty)
projAssetUnionList [AssetUnion]
assets Date
d (A.PoolLevel AssetPerf
assetPerf) Maybe [RateAssumption]
mRate =
let
prjList :: [Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)]
prjList = [ AssetUnion
-> Date
-> AssetPerf
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
projAssetUnion AssetUnion
asset Date
d AssetPerf
assetPerf Maybe [RateAssumption]
mRate | AssetUnion
asset <- [AssetUnion]
assets ]
Either [Char] [(CashFlowFrame, Map CutoffFields BeginBalance)]
results::(Either String [(CF.CashFlowFrame, Map.Map CutoffFields Balance)]) = [Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)]
-> Either [Char] [(CashFlowFrame, Map CutoffFields BeginBalance)]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
sequenceA [Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)]
prjList
in
do
[(CashFlowFrame, Map CutoffFields BeginBalance)]
r <- Either [Char] [(CashFlowFrame, Map CutoffFields BeginBalance)]
results
let cfs :: [CashFlowFrame]
cfs = (CashFlowFrame, Map CutoffFields BeginBalance) -> CashFlowFrame
forall a b. (a, b) -> a
fst ((CashFlowFrame, Map CutoffFields BeginBalance) -> CashFlowFrame)
-> [(CashFlowFrame, Map CutoffFields BeginBalance)]
-> [CashFlowFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(CashFlowFrame, Map CutoffFields BeginBalance)]
r
let bals :: [Map CutoffFields BeginBalance]
bals = (CashFlowFrame, Map CutoffFields BeginBalance)
-> Map CutoffFields BeginBalance
forall a b. (a, b) -> b
snd ((CashFlowFrame, Map CutoffFields BeginBalance)
-> Map CutoffFields BeginBalance)
-> [(CashFlowFrame, Map CutoffFields BeginBalance)]
-> [Map CutoffFields BeginBalance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(CashFlowFrame, Map CutoffFields BeginBalance)]
r
(CashFlowFrame, Map CutoffFields BeginBalance)
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a. a -> Either [Char] a
forall (m :: * -> *) a. Monad m => a -> m a
return ((CashFlowFrame -> CashFlowFrame -> CashFlowFrame)
-> [CashFlowFrame] -> CashFlowFrame
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 CashFlowFrame -> CashFlowFrame -> CashFlowFrame
CF.mergePoolCf2 [CashFlowFrame]
cfs, (BeginBalance -> BeginBalance -> BeginBalance)
-> [Map CutoffFields BeginBalance] -> Map CutoffFields BeginBalance
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
Map.unionsWith BeginBalance -> BeginBalance -> BeginBalance
forall a. Num a => a -> a -> a
(+) [Map CutoffFields BeginBalance]
bals)
projAssetUnionList [AssetUnion]
assets Date
d ApplyAssumptionType
_ Maybe [RateAssumption]
mRate = [Char]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
forall a b. a -> Either a b
Left [Char]
" not implemented on asset level assumption for revolving pool"
projectCashflow :: MixedAsset -> Date -> Map.Map String A.ApplyAssumptionType -> Maybe [RateAssumption]
-> Either String (Map.Map String (CF.CashFlowFrame, Map.Map CutoffFields Balance))
projectCashflow :: MixedAsset
-> Date
-> Map [Char] ApplyAssumptionType
-> Maybe [RateAssumption]
-> Either
[Char] (Map [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
projectCashflow (MixedPool Map [Char] [AssetUnion]
assetMap) Date
asOfDate Map [Char] ApplyAssumptionType
mAssump Maybe [RateAssumption]
mRate
= let
mWithCf :: Map
[Char]
(Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
mWithCf = ([Char]
-> [AssetUnion]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
-> Map [Char] [AssetUnion]
-> Map
[Char]
(Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey
(\[Char]
k [AssetUnion]
astList -> [AssetUnion]
-> Date
-> ApplyAssumptionType
-> Maybe [RateAssumption]
-> Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance)
projAssetUnionList
[AssetUnion]
astList
Date
asOfDate
(case [Char]
-> Map [Char] ApplyAssumptionType -> Maybe ApplyAssumptionType
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup [Char]
k Map [Char] ApplyAssumptionType
mAssump of
Just ApplyAssumptionType
assump -> ApplyAssumptionType
assump
Maybe ApplyAssumptionType
Nothing -> [Char] -> ApplyAssumptionType
forall a. HasCallStack => [Char] -> a
error ([Char]
"Failed to read sub assump:"[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
k))
Maybe [RateAssumption]
mRate)
Map [Char] [AssetUnion]
assetMap
in
Map
[Char]
(Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
-> Either
[Char] (Map [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
Map [Char] (f a) -> f (Map [Char] a)
sequenceA Map
[Char]
(Either [Char] (CashFlowFrame, Map CutoffFields BeginBalance))
mWithCf