| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Waterfall
Documentation
data PoolSource Source #
Constructors
| CollectedInterest | interest |
| CollectedPrincipal | schdule principal |
| CollectedRecoveries | recoveries |
| CollectedPrepayment | prepayment |
| CollectedPrepaymentPenalty | prepayment pentalty |
| CollectedRental | rental from pool |
| CollectedFeePaid | fee from pool |
| CollectedCash | cash from pool |
| NewDefaults | new defaults in balance |
| NewLosses | new losses in balance |
| NewDelinquencies | new delinquencies in balance |
| CurBalance | performing balance |
| CurBegBalance | performing balance at the beginning of the period |
Instances
Constructors
| Transfer (Maybe Limit) AccountName AccountName (Maybe TxnComment) | |
| TransferAndBook (Maybe Limit) AccountName AccountName BookLedger (Maybe TxnComment) | |
| TransferMultiple [(Maybe Limit, AccountName)] AccountName (Maybe TxnComment) | |
| CalcFee [FeeName] | calculate fee due amount in the fee names |
| PayFee (Maybe Limit) AccountName [FeeName] (Maybe ExtraSupport) | pay fee with cash from account with optional limit or extra support |
| PayFeeBySeq (Maybe Limit) AccountName [FeeName] (Maybe ExtraSupport) | pay fee with cash from account with optional limit or extra support |
| CalcAndPayFee (Maybe Limit) AccountName [FeeName] (Maybe ExtraSupport) | combination of CalcFee and PayFee |
| PayFeeResidual (Maybe Limit) AccountName FeeName | pay fee regardless fee due amount Bond - Interest |
| CalcBondInt [BondName] | |
| CalcBondIntBy BondName DealStats DealStats | calculate interest due amount in the bond names,with optional balance and rate |
| PayIntOverInt (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | pay interest over interest only |
| PayInt (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | pay interest with cash from the account with optional limit or extra support |
| PayIntAndBook (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) BookLedger | pay interest with cash from the account with optional limit or extra support |
| PayIntBySeq (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | with sequence |
| PayIntOverIntBySeq (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | pay interest over interest only with sequence |
| AccrueAndPayInt (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | combination of CalcInt and PayInt |
| AccrueAndPayIntBySeq (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | with sequence |
| PayIntResidual (Maybe Limit) AccountName BondName | pay interest to bond regardless interest due |
| PayIntByRateIndex (Maybe Limit) AccountName [BondName] Int (Maybe ExtraSupport) | pay interest to bond by index |
| PayIntByRateIndexBySeq (Maybe Limit) AccountName [BondName] Int (Maybe ExtraSupport) | pay interest to bond by index Bond - Principal |
| CalcBondPrin (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | calculate principal due amount in the bond names |
| CalcBondPrin2 (Maybe Limit) [BondName] | calculate principal due amount in the bond names |
| PayPrinWithDue AccountName [BondName] (Maybe ExtraSupport) | pay principal to bond till due amount |
| PayPrin (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | pay principal to bond via pro-rata |
| PayPrinBySeq (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | pay principal to bond via sequence |
| PayPrinResidual AccountName [BondName] | pay principal regardless predefined balance schedule |
| PayIntPrinBySeq (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | pay int & prin to bonds sequentially |
| AccrueAndPayIntPrinBySeq (Maybe Limit) AccountName [BondName] (Maybe ExtraSupport) | |
| PayPrinGroup (Maybe Limit) AccountName BondName PayOrderBy (Maybe ExtraSupport) | pay bond group with cash from account with optional limit or extra support |
| AccrueIntGroup [BondName] | |
| PayIntGroup (Maybe Limit) AccountName BondName PayOrderBy (Maybe ExtraSupport) | pay bond group with cash from account with optional limit or extra support |
| AccrueAndPayIntGroup (Maybe Limit) AccountName BondName PayOrderBy (Maybe ExtraSupport) | |
| WriteOff (Maybe Limit) BondName | |
| WriteOffAndBook (Maybe Limit) BondName BookLedger | |
| WriteOffBySeq (Maybe Limit) [BondName] | |
| WriteOffBySeqAndBook (Maybe Limit) [BondName] BookLedger | |
| FundWith (Maybe Limit) AccountName BondName | extra more funds from bond and deposit cash to account Pool/Asset change |
| BuyAsset (Maybe Limit) PricingMethod AccountName (Maybe PoolId) | buy asset from revolving assumptions using funds from account |
| BuyAssetFrom (Maybe Limit) PricingMethod AccountName (Maybe String) (Maybe PoolId) | buy asset from specific pool, with revolving assumptions using funds from account |
| LiquidatePool PricingMethod AccountName (Maybe [PoolId]) | sell all assets and deposit proceeds to account TODO include a limit for LIquidatePool Liquidation support |
| LiqSupport (Maybe Limit) LiquidityProviderName LiqDrawType [String] | draw credit and deposit to accountfeebond interest/principal |
| LiqRepay (Maybe Limit) LiqRepayType AccountName LiquidityProviderName | repay liquidity facility |
| LiqYield (Maybe Limit) AccountName LiquidityProviderName | repay compensation to liquidity facility |
| LiqAccrue [LiquidityProviderName] | accure premium/due interest of liquidity facility Rate Swap |
| SwapAccrue CeName | calculate the net amount of swap manually |
| SwapReceive AccountName CeName | receive amount from net amount of swap and deposit to account |
| SwapPay AccountName CeName | pay out net amount from account |
| SwapSettle AccountName CeName | pay & receive net amount of swap with account RateCap |
| CollectRateCap AccountName CeName | collect cash from rate cap and deposit to account Record booking |
| BookBy BookType | book an ledger with book types Pre |
| ActionWithPre Pre [Action] | execute actions if pre is true |
| ActionWithPre2 Pre [Action] [Action] | execute action1 if pre is true ,else execute action2 Trigger |
| RunTrigger DealCycle [String] | update the trigger status during the waterfall execution Debug |
| WatchVal (Maybe String) [DealStats] | inspect vals during the waterfall execution |
| Placeholder (Maybe String) | |
| ChangeStatus (Maybe Pre) DealStatus |
type DistributionSeq = [Action] Source #
data CollectionRule Source #
Constructors
| Collect (Maybe [PoolId]) PoolSource AccountName | collect a pool source from pool collection and deposit to an account |
| CollectByPct (Maybe [PoolId]) PoolSource [(Rate, AccountName)] | collect a pool source from pool collection and deposit to multiple accounts with percentages |
Instances
| FromJSON CollectionRule Source # | |||||
Defined in Waterfall Methods parseJSON :: Value -> Parser CollectionRule # parseJSONList :: Value -> Parser [CollectionRule] # | |||||
| ToJSON CollectionRule Source # | |||||
Defined in Waterfall Methods toJSON :: CollectionRule -> Value # toEncoding :: CollectionRule -> Encoding # toJSONList :: [CollectionRule] -> Value # toEncodingList :: [CollectionRule] -> Encoding # omitField :: CollectionRule -> Bool # | |||||
| Generic CollectionRule Source # | |||||
Defined in Waterfall Associated Types
Methods from :: CollectionRule -> Rep CollectionRule x # to :: Rep CollectionRule x -> CollectionRule # | |||||
| Show CollectionRule Source # | |||||
Defined in Waterfall Methods showsPrec :: Int -> CollectionRule -> ShowS # show :: CollectionRule -> String # showList :: [CollectionRule] -> ShowS # | |||||
| Eq CollectionRule Source # | |||||
Defined in Waterfall Methods (==) :: CollectionRule -> CollectionRule -> Bool # (/=) :: CollectionRule -> CollectionRule -> Bool # | |||||
| Ord CollectionRule Source # | |||||
Defined in Waterfall Methods compare :: CollectionRule -> CollectionRule -> Ordering # (<) :: CollectionRule -> CollectionRule -> Bool # (<=) :: CollectionRule -> CollectionRule -> Bool # (>) :: CollectionRule -> CollectionRule -> Bool # (>=) :: CollectionRule -> CollectionRule -> Bool # max :: CollectionRule -> CollectionRule -> CollectionRule # min :: CollectionRule -> CollectionRule -> CollectionRule # | |||||
| type Rep CollectionRule Source # | |||||
Defined in Waterfall type Rep CollectionRule = D1 ('MetaData "CollectionRule" "Waterfall" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Collect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName))) :+: C1 ('MetaCons "CollectByPct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Rate, AccountName)])))) | |||||
data ActionWhen Source #
Constructors
| EndOfPoolCollection | waterfall executed at the end of pool collection |
| DistributionDay DealStatus | waterfall executed depends on deal status |
| CleanUp | waterfall exectued upon a clean up call |
| OnClosingDay | waterfall executed on deal closing day |
| DefaultDistribution | default waterfall executed |
| RampUp | ramp up |
| WithinTrigger String | waterfall executed within a trigger |
| CustomWaterfall String | custom waterfall |
Instances
| FromJSON ActionWhen Source # | |||||
Defined in Types | |||||
| FromJSONKey ActionWhen Source # | |||||
Defined in Types | |||||
| ToJSON ActionWhen Source # | |||||
Defined in Types Methods toJSON :: ActionWhen -> Value # toEncoding :: ActionWhen -> Encoding # toJSONList :: [ActionWhen] -> Value # toEncodingList :: [ActionWhen] -> Encoding # omitField :: ActionWhen -> Bool # | |||||
| ToJSONKey ActionWhen Source # | |||||
Defined in Types | |||||
| Generic ActionWhen Source # | |||||
Defined in Types Associated Types
| |||||
| Read ActionWhen Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS ActionWhen # readList :: ReadS [ActionWhen] # readPrec :: ReadPrec ActionWhen # readListPrec :: ReadPrec [ActionWhen] # | |||||
| Show ActionWhen Source # | |||||
Defined in Types Methods showsPrec :: Int -> ActionWhen -> ShowS # show :: ActionWhen -> String # showList :: [ActionWhen] -> ShowS # | |||||
| Eq ActionWhen Source # | |||||
Defined in Types | |||||
| Ord ActionWhen Source # | |||||
Defined in Types Methods compare :: ActionWhen -> ActionWhen -> Ordering # (<) :: ActionWhen -> ActionWhen -> Bool # (<=) :: ActionWhen -> ActionWhen -> Bool # (>) :: ActionWhen -> ActionWhen -> Bool # (>=) :: ActionWhen -> ActionWhen -> Bool # max :: ActionWhen -> ActionWhen -> ActionWhen # min :: ActionWhen -> ActionWhen -> ActionWhen # | |||||
| type Rep ActionWhen Source # | |||||
Defined in Types type Rep ActionWhen = D1 ('MetaData "ActionWhen" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "EndOfPoolCollection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistributionDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus))) :+: (C1 ('MetaCons "CleanUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OnClosingDay" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DefaultDistribution" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RampUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WithinTrigger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "CustomWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) | |||||
Constructors
| PDL BookDirection DealStats [(LedgerName, DealStats)] | |
| ByDS LedgerName BookDirection DealStats | |
| Till LedgerName BookDirection DealStats |
Instances
| FromJSON BookType Source # | |||||
| ToJSON BookType Source # | |||||
| Generic BookType Source # | |||||
Defined in Waterfall Associated Types
| |||||
| Show BookType Source # | |||||
| Eq BookType Source # | |||||
| Ord BookType Source # | |||||
Defined in Waterfall | |||||
| type Rep BookType Source # | |||||
Defined in Waterfall type Rep BookType = D1 ('MetaData "BookType" "Waterfall" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PDL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(LedgerName, DealStats)]))) :+: (C1 ('MetaCons "ByDS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LedgerName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "Till" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LedgerName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))))) | |||||
data ExtraSupport Source #
Constructors
| SupportAccount AccountName (Maybe BookLedger) | if there is deficit, draw another account to pay the shortfall |
| SupportLiqFacility LiquidityProviderName | if there is deficit, draw facility's available credit to pay the shortfall |
| MultiSupport [ExtraSupport] | if there is deficit, draw multiple supports (by sequence in the list) to pay the shortfall |
| WithCondition Pre ExtraSupport | support only available if Pre is true |
Instances
| FromJSON ExtraSupport Source # | |||||
Defined in Waterfall | |||||
| ToJSON ExtraSupport Source # | |||||
Defined in Waterfall Methods toJSON :: ExtraSupport -> Value # toEncoding :: ExtraSupport -> Encoding # toJSONList :: [ExtraSupport] -> Value # toEncodingList :: [ExtraSupport] -> Encoding # omitField :: ExtraSupport -> Bool # | |||||
| Generic ExtraSupport Source # | |||||
Defined in Waterfall Associated Types
| |||||
| Show ExtraSupport Source # | |||||
Defined in Waterfall Methods showsPrec :: Int -> ExtraSupport -> ShowS # show :: ExtraSupport -> String # showList :: [ExtraSupport] -> ShowS # | |||||
| Eq ExtraSupport Source # | |||||
Defined in Waterfall | |||||
| Ord ExtraSupport Source # | |||||
Defined in Waterfall Methods compare :: ExtraSupport -> ExtraSupport -> Ordering # (<) :: ExtraSupport -> ExtraSupport -> Bool # (<=) :: ExtraSupport -> ExtraSupport -> Bool # (>) :: ExtraSupport -> ExtraSupport -> Bool # (>=) :: ExtraSupport -> ExtraSupport -> Bool # max :: ExtraSupport -> ExtraSupport -> ExtraSupport # min :: ExtraSupport -> ExtraSupport -> ExtraSupport # | |||||
| type Rep ExtraSupport Source # | |||||
Defined in Waterfall | |||||
data PayOrderBy Source #
Constructors
| ByName | |
| ByProRataCurBal | |
| ByCurrentRate | |
| ByMaturity | |
| ByStartDate | |
| ByCustomNames [String] |
Instances
| FromJSON PayOrderBy Source # | |||||
Defined in Waterfall | |||||
| ToJSON PayOrderBy Source # | |||||
Defined in Waterfall Methods toJSON :: PayOrderBy -> Value # toEncoding :: PayOrderBy -> Encoding # toJSONList :: [PayOrderBy] -> Value # toEncodingList :: [PayOrderBy] -> Encoding # omitField :: PayOrderBy -> Bool # | |||||
| Generic PayOrderBy Source # | |||||
Defined in Waterfall Associated Types
| |||||
| Show PayOrderBy Source # | InverseSeq PayOrderBy | ||||
Defined in Waterfall Methods showsPrec :: Int -> PayOrderBy -> ShowS # show :: PayOrderBy -> String # showList :: [PayOrderBy] -> ShowS # | |||||
| Eq PayOrderBy Source # | |||||
Defined in Waterfall | |||||
| Ord PayOrderBy Source # | |||||
Defined in Waterfall Methods compare :: PayOrderBy -> PayOrderBy -> Ordering # (<) :: PayOrderBy -> PayOrderBy -> Bool # (<=) :: PayOrderBy -> PayOrderBy -> Bool # (>) :: PayOrderBy -> PayOrderBy -> Bool # (>=) :: PayOrderBy -> PayOrderBy -> Bool # max :: PayOrderBy -> PayOrderBy -> PayOrderBy # min :: PayOrderBy -> PayOrderBy -> PayOrderBy # | |||||
| type Rep PayOrderBy Source # | |||||
Defined in Waterfall type Rep PayOrderBy = D1 ('MetaData "PayOrderBy" "Waterfall" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "ByName" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ByProRataCurBal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByCurrentRate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ByMaturity" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ByStartDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByCustomNames" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))))) | |||||