Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cashflow
Synopsis
- data CashFlowFrame
- = CashFlowFrame BeginStatus [TsRow]
- | MultiCashFlowFrame (Map String [CashFlowFrame])
- type Principals = [Principal]
- type Interests = [Interest]
- type Amount = Balance
- combine :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
- mergePoolCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
- sumTsCF :: [TsRow] -> Date -> TsRow
- tsSetLoss :: Balance -> TsRow -> TsRow
- tsSetRecovery :: Balance -> TsRow -> TsRow
- sizeCashFlowFrame :: CashFlowFrame -> Int
- aggTsByDates :: [TsRow] -> [Date] -> [TsRow]
- emptyCashFlowFrame :: CashFlowFrame -> Bool
- mflowInterest :: TsRow -> Balance
- mflowPrincipal :: TsRow -> Balance
- mflowRecovery :: TsRow -> Balance
- mflowPrepayment :: TsRow -> Balance
- mflowRental :: TsRow -> Amount
- mflowRate :: TsRow -> IRate
- sumPoolFlow :: CashFlowFrame -> PoolSource -> Balance
- splitTrs :: Rate -> [TsRow] -> [TsRow]
- aggregateTsByDate :: [TsRow] -> [TsRow] -> [TsRow]
- mflowDefault :: TsRow -> Balance
- mflowLoss :: TsRow -> Balance
- getDatesCashFlowFrame :: CashFlowFrame -> [Date]
- lookupSource :: TsRow -> PoolSource -> Balance
- lookupSourceM :: Balance -> Maybe TsRow -> PoolSource -> Balance
- combineTss :: [TsRow] -> [TsRow] -> [TsRow] -> [TsRow]
- mflowBegBalance :: TsRow -> Balance
- tsDefaultBal :: TsRow -> Either String Balance
- mflowBorrowerNum :: TsRow -> Maybe BorrowerNum
- mflowPrepaymentPenalty :: TsRow -> Balance
- tsRowBalance :: Lens' TsRow Balance
- emptyTsRow :: Date -> TsRow -> TsRow
- mflowAmortAmount :: TsRow -> Balance
- tsTotalCash :: TsRow -> Balance
- setPrepaymentPenalty :: Balance -> TsRow -> TsRow
- setPrepaymentPenaltyFlow :: [Balance] -> [TsRow] -> [TsRow]
- getDate :: TimeSeries ts => ts -> Date
- getTxnLatestAsOf :: CashFlowFrame -> Date -> Maybe TsRow
- totalPrincipal :: CashFlowFrame -> Balance
- mflowWeightAverageBalance :: Date -> Date -> [TsRow] -> Balance
- tsDate :: Lens' TsRow Date
- totalLoss :: CashFlowFrame -> Balance
- totalDefault :: CashFlowFrame -> Balance
- totalRecovery :: CashFlowFrame -> Balance
- firstDate :: CashFlowFrame -> Date
- shiftCfToStartDate :: Date -> CashFlowFrame -> CashFlowFrame
- cfInsertHead :: TsRow -> CashFlowFrame -> CashFlowFrame
- buildBegTsRow :: Date -> TsRow -> TsRow
- insertBegTsRow :: Date -> CashFlowFrame -> CashFlowFrame
- tsCumDefaultBal :: TsRow -> Maybe Balance
- tsCumDelinqBal :: TsRow -> Maybe Balance
- tsCumLossBal :: TsRow -> Maybe Balance
- tsCumRecoveriesBal :: TsRow -> Maybe Balance
- data TsRow
- = CashFlow Date Amount
- | BondFlow Date Balance Principal Interest
- | MortgageFlow Date Balance Principal Interest Prepayment Default Recovery Loss IRate (Maybe BorrowerNum) (Maybe PrepaymentPenalty) (Maybe CumulativeStat)
- | MortgageDelinqFlow Date Balance Principal Interest Prepayment Delinquent Default Recovery Loss IRate (Maybe BorrowerNum) (Maybe PrepaymentPenalty) (Maybe CumulativeStat)
- | LoanFlow Date Balance Principal Interest Prepayment Default Recovery Loss IRate (Maybe CumulativeStat)
- | LeaseFlow Date Balance Rental Default
- | FixedFlow Date Balance NewDepreciation Depreciation Balance Balance
- | ReceivableFlow Date Balance AccuredFee Principal FeePaid Default Recovery Loss (Maybe CumulativeStat)
- cfAt :: CashFlowFrame -> Int -> Maybe TsRow
- cutoffTrs :: Date -> [TsRow] -> ([TsRow], Map CutoffFields Balance)
- patchCumulative :: CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow]
- extendTxns :: TsRow -> [Date] -> [TsRow]
- dropTailEmptyTxns :: [TsRow] -> [TsRow]
- cashflowTxn :: Lens' CashFlowFrame [TsRow]
- clawbackInt :: Balance -> [TsRow] -> [TsRow]
- scaleTsRow :: Rational -> TsRow -> TsRow
- mflowFeePaid :: TsRow -> Amount
- currentCumulativeStat :: [TsRow] -> CumulativeStat
- patchCumulativeAtInit :: Maybe CumulativeStat -> [TsRow] -> [TsRow]
- mergeCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
- buildStartTsRow :: CashFlowFrame -> Maybe TsRow
- txnCumulativeStats :: Lens' TsRow (Maybe CumulativeStat)
- consolidateCashFlow :: CashFlowFrame -> CashFlowFrame
- cfBeginStatus :: Lens' CashFlowFrame BeginStatus
- getBegBalCashFlowFrame :: CashFlowFrame -> Balance
- splitCashFlowFrameByDate :: CashFlowFrame -> Date -> SplitType -> (CashFlowFrame, CashFlowFrame)
- mergePoolCf2 :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame
- buildBegBal :: [TsRow] -> Balance
- extendCashFlow :: Date -> CashFlowFrame -> CashFlowFrame
- patchBalance :: (Balance, Maybe CumulativeStat) -> [TsRow] -> [TsRow] -> [TsRow]
- splitPoolCashflowByDate :: PoolCashflow -> Date -> SplitType -> (PoolCashflow, PoolCashflow)
- getAllDatesCashFlowFrame :: CashFlowFrame -> [Date]
- splitCf :: Rate -> CashFlowFrame -> CashFlowFrame
- cutoffCashflow :: Date -> Dates -> CashFlowFrame -> CashFlowFrame
- type AssetCashflow = CashFlowFrame
- type PoolCashflow = (AssetCashflow, Maybe [AssetCashflow])
- emptyCashflow :: CashFlowFrame
- isEmptyRow2 :: TsRow -> Bool
Documentation
data CashFlowFrame Source #
Constructors
CashFlowFrame BeginStatus [TsRow] | |
MultiCashFlowFrame (Map String [CashFlowFrame]) |
Instances
type Principals = [Principal] Source #
combine :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame Source #
mergePoolCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame Source #
agg cashflow (but not updating the cumulative stats)
sizeCashFlowFrame :: CashFlowFrame -> Int Source #
mflowInterest :: TsRow -> Balance Source #
mflowPrincipal :: TsRow -> Balance Source #
mflowRecovery :: TsRow -> Balance Source #
mflowPrepayment :: TsRow -> Balance Source #
mflowRental :: TsRow -> Amount Source #
sumPoolFlow :: CashFlowFrame -> PoolSource -> Balance Source #
lookup a pool source from a row
mflowDefault :: TsRow -> Balance Source #
getDatesCashFlowFrame :: CashFlowFrame -> [Date] Source #
lookupSource :: TsRow -> PoolSource -> Balance Source #
lookupSourceM :: Balance -> Maybe TsRow -> PoolSource -> Balance Source #
mflowBegBalance :: TsRow -> Balance Source #
mflowBorrowerNum :: TsRow -> Maybe BorrowerNum Source #
get borrower numfer for Mortgage Flow
mflowPrepaymentPenalty :: TsRow -> Balance Source #
get prepayment penalty for a cashflow record
mflowAmortAmount :: TsRow -> Balance Source #
calculate amortized amount for cashflow (for defaults only)
tsTotalCash :: TsRow -> Balance Source #
setPrepaymentPenaltyFlow :: [Balance] -> [TsRow] -> [TsRow] Source #
split single cashflow record by a rate
getDate :: TimeSeries ts => ts -> Date Source #
getTxnLatestAsOf :: CashFlowFrame -> Date -> Maybe TsRow Source #
totalPrincipal :: CashFlowFrame -> Balance Source #
merge two cashflow frame but no patching beg balance
totalLoss :: CashFlowFrame -> Balance Source #
totalDefault :: CashFlowFrame -> Balance Source #
totalRecovery :: CashFlowFrame -> Balance Source #
firstDate :: CashFlowFrame -> Date Source #
shiftCfToStartDate :: Date -> CashFlowFrame -> CashFlowFrame Source #
sum a single pool source from a cashflow frame
cfInsertHead :: TsRow -> CashFlowFrame -> CashFlowFrame Source #
insertBegTsRow :: Date -> CashFlowFrame -> CashFlowFrame Source #
Constructors
CashFlow Date Amount | |
BondFlow Date Balance Principal Interest | |
MortgageFlow Date Balance Principal Interest Prepayment Default Recovery Loss IRate (Maybe BorrowerNum) (Maybe PrepaymentPenalty) (Maybe CumulativeStat) | |
MortgageDelinqFlow Date Balance Principal Interest Prepayment Delinquent Default Recovery Loss IRate (Maybe BorrowerNum) (Maybe PrepaymentPenalty) (Maybe CumulativeStat) | |
LoanFlow Date Balance Principal Interest Prepayment Default Recovery Loss IRate (Maybe CumulativeStat) | |
LeaseFlow Date Balance Rental Default | |
FixedFlow Date Balance NewDepreciation Depreciation Balance Balance | |
ReceivableFlow Date Balance AccuredFee Principal FeePaid Default Recovery Loss (Maybe CumulativeStat) |
Instances
TimeSeries TsRow Source # | |
Defined in Cashflow Methods cmp :: TsRow -> TsRow -> Ordering Source # sameDate :: TsRow -> TsRow -> Bool Source # getDate :: TsRow -> Date Source # getDates :: [TsRow] -> [Date] Source # filterByDate :: [TsRow] -> Date -> [TsRow] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [TsRow] -> [TsRow] Source # cutBy :: CutoffType -> DateDirection -> Date -> [TsRow] -> [TsRow] Source # cmpWith :: TsRow -> Date -> Ordering Source # isAfter :: TsRow -> Date -> Bool Source # isOnAfter :: TsRow -> Date -> Bool Source # isBefore :: TsRow -> Date -> Bool Source # isOnBefore :: TsRow -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [TsRow] -> ([TsRow], [TsRow]) Source # | |
FromJSON TsRow Source # | |
ToJSON TsRow Source # | |
Semigroup TsRow Source # | |
Generic TsRow Source # | |
Show TsRow Source # | |
NFData TsRow Source # | |
Eq TsRow Source # | |
Ord TsRow Source # | |
ToSchema TsRow Source # | |
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy TsRow -> Declare (Definitions Schema) NamedSchema # | |
type Rep TsRow Source # | |
patchCumulative :: CumulativeStat -> [TsRow] -> [TsRow] -> [TsRow] Source #
split cashflow by rate while build missing defaults/losses stats
dropTailEmptyTxns :: [TsRow] -> [TsRow] Source #
mflowFeePaid :: TsRow -> Amount Source #
currentCumulativeStat :: [TsRow] -> CumulativeStat Source #
mergeCf :: CashFlowFrame -> CashFlowFrame -> CashFlowFrame Source #
cfBeginStatus :: Lens' CashFlowFrame BeginStatus Source #
splitCashFlowFrameByDate :: CashFlowFrame -> Date -> SplitType -> (CashFlowFrame, CashFlowFrame) Source #
buildBegBal :: [TsRow] -> Balance Source #
extendCashFlow :: Date -> CashFlowFrame -> CashFlowFrame Source #
splitPoolCashflowByDate :: PoolCashflow -> Date -> SplitType -> (PoolCashflow, PoolCashflow) Source #
getAllDatesCashFlowFrame :: CashFlowFrame -> [Date] Source #
splitCf :: Rate -> CashFlowFrame -> CashFlowFrame Source #
cutoffCashflow :: Date -> Dates -> CashFlowFrame -> CashFlowFrame Source #
type AssetCashflow = CashFlowFrame Source #
type PoolCashflow = (AssetCashflow, Maybe [AssetCashflow]) Source #
isEmptyRow2 :: TsRow -> Bool Source #
Remove empty cashflow from the tail