Skip to content

Commit

Permalink
Fix FixedAsset Flow Aggregation
Browse files Browse the repository at this point in the history
  • Loading branch information
yellowbean committed Dec 24, 2023
1 parent 6c5f22d commit 8c02c53
Show file tree
Hide file tree
Showing 6 changed files with 24 additions and 13 deletions.
2 changes: 1 addition & 1 deletion src/Asset.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ class (Show a,IR.UseRate a) => Asset a where
calcAlignDate ast d = let
payDates = getPaymentDates ast 0
remainTerms = getRemainTerms ast
benchDate = reverse payDates!!pred remainTerms -- `debug` ("\nPayDates"++show payDates++"\nremain terms"++ show remainTerms)
benchDate = reverse payDates!!pred remainTerms `debug` ("\nPayDates"++show payDates++"\nremain terms"++ show remainTerms)
offset = daysBetween benchDate d
in
T.addDays offset $ getOriginDate ast
Expand Down
14 changes: 14 additions & 0 deletions src/AssetClass/FixedAsset.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE InstanceSigs #-}

module AssetClass.FixedAsset
()
Expand Down Expand Up @@ -31,6 +32,8 @@ import AssetClass.AssetBase
import Debug.Trace
import AssetClass.AssetCashflow
import qualified Asset as Ast
import Asset (Asset(projCashflow))
import Assumptions (AssetDelinqPerfAssumption(DummyDelinqAssump))
debug = flip trace

calcAmortAmt ::FixedAsset -> [Balance]
Expand All @@ -53,6 +56,17 @@ calcAmortBals fa@(FixedAsset fai@FixedAssetInfo{originBalance=ob, accRule=ar, or


instance Ast.Asset FixedAsset where

calcCashflow fa@(FixedAsset {}) asOfDay _ =
let
(scheduleFlow, _) = projCashflow
fa
asOfDay
(A.FixedAssetAssump (mkTs []) (mkTs []), A.DummyDelinqAssump, A.DummyDefaultAssump)
Nothing
in
scheduleFlow

getCurrentBal fa@(FixedAsset fai@FixedAssetInfo{originBalance=ob, accRule=ar, originTerm=ot
,residualBalance=rb ,capacity=cap} rt)
= calcAmortBals fa!!(ot-rt)
Expand Down
5 changes: 5 additions & 0 deletions src/Cashflow.hs
Original file line number Diff line number Diff line change
Expand Up @@ -266,6 +266,8 @@ addTsCF (MortgageDelinqFlow d1 b1 p1 i1 prep1 delinq1 def1 rec1 los1 rat1 mbn1 p
addTsCF (LoanFlow d1 b1 p1 i1 prep1 def1 rec1 los1 rat1 st1) (LoanFlow _ b2 p2 i2 prep2 def2 rec2 los2 rat2 st2)
= LoanFlow d1 (min b1 b2) (p1 + p2) (i1 + i2) (prep1 + prep2) (def1 + def2) (rec1 + rec2) (los1+los2) (fromRational (weightedBy [b1,b2] (toRational <$> [rat1,rat2]))) (maxStats st1 st2)
addTsCF (LeaseFlow d1 b1 r1) (LeaseFlow d2 b2 r2) = LeaseFlow d1 (min b1 b2) (r1 + r2)
addTsCF (FixedFlow d1 b1 dep1 cd1 u1 c1) (FixedFlow d2 b2 dep2 cd2 u2 c2)
= FixedFlow d1 (min b1 b2) (dep1 + dep2) (cd1 + cd2) u2 (c1 + c2)

sumTs :: [TsRow] -> Date -> TsRow
sumTs trs = tsSetDate (foldr1 addTs trs)
Expand Down Expand Up @@ -574,17 +576,20 @@ viewTsRow _d (FixedFlow a b c d e f ) = FixedFlow _d b 0 0 0 0

-- ^ given a cashflow,build a new cf row with begin balance
buildBegTsRow :: Date -> TsRow -> TsRow
buildBegTsRow d flow@FixedFlow{} = flow
buildBegTsRow d tr =
let
r = tsSetBalance (mflowBalance tr + mflowAmortAmount tr) (emptyTsRow d tr)
rate = mflowRate tr
in
tsSetRate rate r


tsSetRate :: IRate -> TsRow -> TsRow
tsSetRate _r (MortgageDelinqFlow a b c d e f g h i j k l m) = MortgageDelinqFlow a b c d e f g h i _r k l m
tsSetRate _r (MortgageFlow a b c d e f g h i j k l) = MortgageFlow a b c d e f g h _r j k l
tsSetRate _r (LoanFlow a b c d e f g i j k) = LoanFlow a b c d e f g i _r k
tsSetRate _r (FixedFlow {} ) = error "Not implement set rate for FixedFlow"


insertBegTsRow :: Date -> CashFlowFrame -> CashFlowFrame
Expand Down
9 changes: 0 additions & 9 deletions src/Deal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -616,15 +616,6 @@ runPool (P.Pool as Nothing Nothing asof _ _) (Just (AP.ByIndex idxAssumps)) mRat
in
zipWith (\x a -> P.projCashflow x asof a mRates) as _assumps

-- mixed asset
-- runPool (P.Pool mixedAsset Nothing asof _ _) (Just (AP.ByName assumpM)) mRates =
-- let
-- r = projectCashflow (head mixedAsset) asof assumpM mRates
--
-- in
-- r


-- safe net to catch other cases
runPool _a _b _c = error $ "Failed to match" ++ show _a ++ show _b ++ show _c

Expand Down
4 changes: 2 additions & 2 deletions src/Deal/DealAction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -468,12 +468,12 @@ performActionWrap d
(assetBought,poolAfterBought) = buyRevolvingPool d purchaseRatios assetForSale -- `debug` ("purchase ratio"++ show purchaseRatios)
newAccMap = Map.adjust (A.draw purchaseAmt d PurchaseAsset) accName accsMap

(CashFlowFrame newBoughtTxn) = fst $ projAssetUnionList [updateOriginDate2 d ast | ast <- assetBought ] d perfAssumps mRates -- `debug` ("Asset bought"++ show assetBought)
(CashFlowFrame newBoughtTxn) = fst $ projAssetUnionList [updateOriginDate2 d ast | ast <- assetBought ] d perfAssumps mRates `debug` ("Asset bought"++ show [updateOriginDate2 d ast | ast <- assetBought ])
-- newPcf = CF.CashFlowFrame $ CF.combineTss [] (tr:trs) newBoughtTxn -- `debug` ("reolvoing first txn\n"++ show (head newBoughtTxn))
newPcf = let
pIdToChange = fromMaybe PoolConsol pId
in
Map.adjust (\(CF.CashFlowFrame trs) -> CF.CashFlowFrame (CF.combineTss [] trs newBoughtTxn)) pIdToChange pFlowMap
Map.adjust (\(CF.CashFlowFrame trs) -> CF.CashFlowFrame (CF.combineTss [] trs newBoughtTxn)) pIdToChange pFlowMap `debug` ("date"++show d ++">>Asset bought txn"++ show newBoughtTxn)
newRc = rc {runPoolFlow = newPcf
,revolvingAssump = Just (poolAfterBought, perfAssumps)}

Expand Down
3 changes: 2 additions & 1 deletion src/Deal/DealQuery.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,7 @@ patchDateToStats d t
Min dss -> Min $ [ patchDateToStats d ds | ds <- dss ]
Max dss -> Max $ [ patchDateToStats d ds | ds <- dss ]
Factor _ds r -> Factor (patchDateToStats d _ds) r
FloorWithZero ds -> FloorWithZero (patchDateToStats d ds)
UseCustomData n -> CustomData n d
CurrentPoolBorrowerNum mPns -> FutureCurrentPoolBorrowerNum d mPns
FeeTxnAmt ns mCmt -> FeeTxnAmtBy d ns mCmt
Expand Down Expand Up @@ -235,7 +236,7 @@ queryDeal t@TestDeal{accounts=accMap, bonds=bndMap, fees=feeMap, ledgers=ledgerM
ReserveAccGapAt d ans ->
max
0
$ (-) (sum $ calcTargetAmount t d <$> (accMap Map.!) <$> ans ) (queryDeal t (AccBalance ans))
$ (-) (sum $ calcTargetAmount t d . (accMap Map.!) <$> ans ) (queryDeal t (AccBalance ans))

FutureCurrentPoolBalance mPns ->
let
Expand Down

0 comments on commit 8c02c53

Please sign in to comment.