Safe Haskell | None |
---|---|
Language | Haskell2010 |
Assumptions
Synopsis
- data BondPricingInput
- = DiscountCurve PricingDate Ts
- | RunZSpread Ts (Map BondName (Date, Rational))
- | DiscountRate PricingDate Rate
- | IrrInput (Map BondName IrrType)
- data IrrType
- = HoldingBond HistoryCash CurrentHolding (Maybe (Date, BondPricingMethod))
- | BuyBond Date BondPricingMethod TradeType (Maybe (Date, BondPricingMethod))
- data AssumptionInput
- data ApplyAssumptionType
- = PoolLevel AssetPerf
- | ByIndex [StratPerfByIdx]
- | ByName (Map PoolId AssetPerf)
- | ByPoolId (Map PoolId ApplyAssumptionType)
- | ByObligor [ObligorStrategy]
- | ByDealName (Map DealName (ApplyAssumptionType, NonPerfAssumption))
- lookupAssumptionByIdx :: [StratPerfByIdx] -> Int -> Either String AssetPerf
- lookupRate :: [RateAssumption] -> Floater -> Date -> Either String IRate
- data AssetPerfAssumption
- = MortgageAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
- | MortgageDeqAssump (Maybe AssetDelinquencyAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
- | LeaseAssump (Maybe LeaseDefaultType) LeaseAssetGapAssump LeaseAssetRentAssump LeaseEndType
- | LoanAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
- | InstallmentAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
- | ReceivableAssump (Maybe AssetDefaultAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress)
- | FixedAssetAssump Ts Ts (Maybe Int)
- data ExtraStress = ExtraStress {
- defaultFactors :: Maybe Ts
- prepaymentFactors :: Maybe Ts
- poolHairCut :: Maybe [(PoolSource, Rate)]
- data RevolvingAssumption
- data AssetPrepayAssumption
- data AssetDefaultAssumption
- data RecoveryAssumption
- = Recovery (Rate, Int)
- | RecoveryTiming (Rate, [Rate])
- | RecoveryByDays Rate [(Int, Rate)]
- getRateAssumption :: [RateAssumption] -> Index -> Maybe RateAssumption
- projRates :: IRate -> RateType -> Maybe [RateAssumption] -> [Date] -> Either String [IRate]
- lookupRate0 :: [RateAssumption] -> Index -> Date -> Either String IRate
- data LeaseAssetGapAssump
- data LeaseAssetRentAssump
- data NonPerfAssumption = NonPerfAssumption {
- stopRunBy :: Maybe StopBy
- projectedExpense :: Maybe [(FeeName, Ts)]
- callWhen :: Maybe [CallOpt]
- revolving :: Maybe RevolvingAssumption
- interest :: Maybe [RateAssumption]
- inspectOn :: Maybe [InspectType]
- buildFinancialReport :: Maybe DatePattern
- pricing :: Maybe BondPricingInput
- fireTrigger :: Maybe [(Date, DealCycle, String)]
- makeWholeWhen :: Maybe (Date, Spread, Table Float Spread)
- issueBondSchedule :: Maybe [TsPoint IssueBondEvent]
- refinance :: Maybe [TsPoint RefiEvent]
- type AssetPerf = (AssetPerfAssumption, AssetDelinqPerfAssumption, AssetDefaultedPerfAssumption)
- data AssetDelinquencyAssumption
- data AssetDelinqPerfAssumption = DummyDelinqAssump
- data AssetDefaultedPerfAssumption
- data IssueBondEvent
- data TagMatchRule
- data ObligorStrategy
- = ObligorById [String] AssetPerf
- | ObligorByTag [ObligorTagStr] TagMatchRule AssetPerf
- | ObligorByField [FieldMatchRule] AssetPerf
- | ObligorByDefault AssetPerf
- data RefiEvent
- data InspectType
- data FieldMatchRule
- data CallOpt
- = LegacyOpts [CallOption]
- | CallPredicate [Pre]
- | CallOnDates DatePattern [Pre]
- _MortgageAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress)
- _MortgageDeqAssump :: Prism' AssetPerfAssumption (Maybe AssetDelinquencyAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress)
- _LeaseAssump :: Prism' AssetPerfAssumption (Maybe LeaseDefaultType, LeaseAssetGapAssump, LeaseAssetRentAssump, LeaseEndType)
- _LoanAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress)
- _InstallmentAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress)
- _ReceivableAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe RecoveryAssumption, Maybe ExtraStress)
- _FixedAssetAssump :: Prism' AssetPerfAssumption (Ts, Ts, Maybe Int)
- stressDefaultAssump :: Rate -> AssetDefaultAssumption -> AssetDefaultAssumption
- applyAssumptionTypeAssetPerf :: Traversal' ApplyAssumptionType AssetPerf
- data TradeType
- data LeaseEndType
- data LeaseDefaultType
- stressPrepaymentAssump :: Rate -> AssetPrepayAssumption -> AssetPrepayAssumption
- data StopBy
Documentation
data BondPricingInput Source #
Constructors
DiscountCurve PricingDate Ts | PV curve used to discount bond cashflow and a PV date where cashflow discounted to |
RunZSpread Ts (Map BondName (Date, Rational)) | PV curve as well as bond trading price with a deal used to calc Z - spread |
DiscountRate PricingDate Rate | |
IrrInput | OASInput Date BondName Balance [Spread] (Map.Map String Ts) -- ^ only works in multiple assumption request |
Instances
FromJSON BondPricingInput Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser BondPricingInput # parseJSONList :: Value -> Parser [BondPricingInput] # | |||||
ToJSON BondPricingInput Source # | |||||
Defined in Assumptions Methods toJSON :: BondPricingInput -> Value # toEncoding :: BondPricingInput -> Encoding # toJSONList :: [BondPricingInput] -> Value # toEncodingList :: [BondPricingInput] -> Encoding # omitField :: BondPricingInput -> Bool # | |||||
Generic BondPricingInput Source # | |||||
Defined in Assumptions Associated Types
Methods from :: BondPricingInput -> Rep BondPricingInput x # to :: Rep BondPricingInput x -> BondPricingInput # | |||||
Show BondPricingInput Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> BondPricingInput -> ShowS # show :: BondPricingInput -> String # showList :: [BondPricingInput] -> ShowS # | |||||
type Rep BondPricingInput Source # | |||||
Defined in Assumptions |
Constructors
HoldingBond HistoryCash CurrentHolding (Maybe (Date, BondPricingMethod)) | |
BuyBond Date BondPricingMethod TradeType (Maybe (Date, BondPricingMethod)) |
data AssumptionInput Source #
Constructors
Single ApplyAssumptionType NonPerfAssumption | one assumption request |
Multiple (Map String ApplyAssumptionType) NonPerfAssumption | multiple assumption request in a single request |
Instances
data ApplyAssumptionType Source #
Constructors
PoolLevel AssetPerf | assumption apply to all assets in the pool |
ByIndex [StratPerfByIdx] | assumption which only apply to a set of assets in the pool |
ByName (Map PoolId AssetPerf) | assumption for a named pool |
ByPoolId (Map PoolId ApplyAssumptionType) | assumption for a pool |
ByObligor [ObligorStrategy] | assumption for a set of obligors |
ByDealName (Map DealName (ApplyAssumptionType, NonPerfAssumption)) | assumption for a named deal |
Instances
FromJSON ApplyAssumptionType Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser ApplyAssumptionType # parseJSONList :: Value -> Parser [ApplyAssumptionType] # | |||||
ToJSON ApplyAssumptionType Source # | |||||
Defined in Assumptions Methods toJSON :: ApplyAssumptionType -> Value # toEncoding :: ApplyAssumptionType -> Encoding # toJSONList :: [ApplyAssumptionType] -> Value # toEncodingList :: [ApplyAssumptionType] -> Encoding # omitField :: ApplyAssumptionType -> Bool # | |||||
Generic ApplyAssumptionType Source # | |||||
Defined in Assumptions Associated Types
Methods from :: ApplyAssumptionType -> Rep ApplyAssumptionType x # to :: Rep ApplyAssumptionType x -> ApplyAssumptionType # | |||||
Show ApplyAssumptionType Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> ApplyAssumptionType -> ShowS # show :: ApplyAssumptionType -> String # showList :: [ApplyAssumptionType] -> ShowS # | |||||
type Rep ApplyAssumptionType Source # | |||||
Defined in Assumptions |
lookupRate :: [RateAssumption] -> Floater -> Date -> Either String IRate Source #
lookup rate from rate assumption with index
data AssetPerfAssumption Source #
Constructors
MortgageAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress) | |
MortgageDeqAssump (Maybe AssetDelinquencyAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress) | |
LeaseAssump (Maybe LeaseDefaultType) LeaseAssetGapAssump LeaseAssetRentAssump LeaseEndType | |
LoanAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress) | |
InstallmentAssump (Maybe AssetDefaultAssumption) (Maybe AssetPrepayAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress) | |
ReceivableAssump (Maybe AssetDefaultAssumption) (Maybe RecoveryAssumption) (Maybe ExtraStress) | |
FixedAssetAssump Ts Ts (Maybe Int) |
Instances
FromJSON AssetPerfAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser AssetPerfAssumption # parseJSONList :: Value -> Parser [AssetPerfAssumption] # | |||||
ToJSON AssetPerfAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: AssetPerfAssumption -> Value # toEncoding :: AssetPerfAssumption -> Encoding # toJSONList :: [AssetPerfAssumption] -> Value # toEncodingList :: [AssetPerfAssumption] -> Encoding # omitField :: AssetPerfAssumption -> Bool # | |||||
Generic AssetPerfAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: AssetPerfAssumption -> Rep AssetPerfAssumption x # to :: Rep AssetPerfAssumption x -> AssetPerfAssumption # | |||||
Read AssetPerfAssumption Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS AssetPerfAssumption # readList :: ReadS [AssetPerfAssumption] # | |||||
Show AssetPerfAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> AssetPerfAssumption -> ShowS # show :: AssetPerfAssumption -> String # showList :: [AssetPerfAssumption] -> ShowS # | |||||
type Rep AssetPerfAssumption Source # | |||||
Defined in Assumptions type Rep AssetPerfAssumption = D1 ('MetaData "AssetPerfAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "MortgageAssump" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetDefaultAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetPrepayAssumption))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RecoveryAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExtraStress)))) :+: (C1 ('MetaCons "MortgageDeqAssump" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetDelinquencyAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetPrepayAssumption))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RecoveryAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExtraStress)))) :+: C1 ('MetaCons "LeaseAssump" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LeaseDefaultType)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LeaseAssetGapAssump)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LeaseAssetRentAssump) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LeaseEndType))))) :+: ((C1 ('MetaCons "LoanAssump" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetDefaultAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetPrepayAssumption))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RecoveryAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExtraStress)))) :+: C1 ('MetaCons "InstallmentAssump" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetDefaultAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetPrepayAssumption))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RecoveryAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExtraStress))))) :+: (C1 ('MetaCons "ReceivableAssump" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AssetDefaultAssumption)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RecoveryAssumption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExtraStress)))) :+: C1 ('MetaCons "FixedAssetAssump" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))) |
data ExtraStress Source #
Constructors
ExtraStress | |
Fields
|
Instances
FromJSON ExtraStress Source # | |||||
Defined in Assumptions | |||||
ToJSON ExtraStress Source # | |||||
Defined in Assumptions Methods toJSON :: ExtraStress -> Value # toEncoding :: ExtraStress -> Encoding # toJSONList :: [ExtraStress] -> Value # toEncodingList :: [ExtraStress] -> Encoding # omitField :: ExtraStress -> Bool # | |||||
Generic ExtraStress Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read ExtraStress Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS ExtraStress # readList :: ReadS [ExtraStress] # readPrec :: ReadPrec ExtraStress # readListPrec :: ReadPrec [ExtraStress] # | |||||
Show ExtraStress Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> ExtraStress -> ShowS # show :: ExtraStress -> String # showList :: [ExtraStress] -> ShowS # | |||||
type Rep ExtraStress Source # | |||||
Defined in Assumptions type Rep ExtraStress = D1 ('MetaData "ExtraStress" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "ExtraStress" 'PrefixI 'True) (S1 ('MetaSel ('Just "defaultFactors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ts)) :*: (S1 ('MetaSel ('Just "prepaymentFactors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ts)) :*: S1 ('MetaSel ('Just "poolHairCut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [(PoolSource, Rate)]))))) |
data RevolvingAssumption Source #
Constructors
AvailableAssets RevolvingPool ApplyAssumptionType | |
AvailableAssetsBy (Map String (RevolvingPool, ApplyAssumptionType)) |
Instances
FromJSON RevolvingAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser RevolvingAssumption # parseJSONList :: Value -> Parser [RevolvingAssumption] # | |||||
ToJSON RevolvingAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: RevolvingAssumption -> Value # toEncoding :: RevolvingAssumption -> Encoding # toJSONList :: [RevolvingAssumption] -> Value # toEncodingList :: [RevolvingAssumption] -> Encoding # omitField :: RevolvingAssumption -> Bool # | |||||
Generic RevolvingAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: RevolvingAssumption -> Rep RevolvingAssumption x # to :: Rep RevolvingAssumption x -> RevolvingAssumption # | |||||
Show RevolvingAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> RevolvingAssumption -> ShowS # show :: RevolvingAssumption -> String # showList :: [RevolvingAssumption] -> ShowS # | |||||
type Rep RevolvingAssumption Source # | |||||
Defined in Assumptions type Rep RevolvingAssumption = D1 ('MetaData "RevolvingAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "AvailableAssets" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RevolvingPool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ApplyAssumptionType)) :+: C1 ('MetaCons "AvailableAssetsBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String (RevolvingPool, ApplyAssumptionType))))) |
data AssetPrepayAssumption Source #
Constructors
PrepaymentConstant Rate | |
PrepaymentCPR Rate | |
PrepaymentVec [Rate] | |
PrepaymentVecPadding [Rate] | |
PrepayByAmt (Balance, [Rate]) | |
PrepayStressByTs Ts AssetPrepayAssumption | |
PrepaymentPSA Rate | |
PrepaymentByTerm [[Rate]] |
Instances
FromJSON AssetPrepayAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser AssetPrepayAssumption # parseJSONList :: Value -> Parser [AssetPrepayAssumption] # | |||||
ToJSON AssetPrepayAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: AssetPrepayAssumption -> Value # toEncoding :: AssetPrepayAssumption -> Encoding # toJSONList :: [AssetPrepayAssumption] -> Value # toEncodingList :: [AssetPrepayAssumption] -> Encoding # omitField :: AssetPrepayAssumption -> Bool # | |||||
Generic AssetPrepayAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: AssetPrepayAssumption -> Rep AssetPrepayAssumption x # to :: Rep AssetPrepayAssumption x -> AssetPrepayAssumption # | |||||
Read AssetPrepayAssumption Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS AssetPrepayAssumption # readList :: ReadS [AssetPrepayAssumption] # | |||||
Show AssetPrepayAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> AssetPrepayAssumption -> ShowS # show :: AssetPrepayAssumption -> String # showList :: [AssetPrepayAssumption] -> ShowS # | |||||
type Rep AssetPrepayAssumption Source # | |||||
Defined in Assumptions type Rep AssetPrepayAssumption = D1 ('MetaData "AssetPrepayAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "PrepaymentConstant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PrepaymentCPR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))) :+: (C1 ('MetaCons "PrepaymentVec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate])) :+: C1 ('MetaCons "PrepaymentVecPadding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate])))) :+: ((C1 ('MetaCons "PrepayByAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Balance, [Rate]))) :+: C1 ('MetaCons "PrepayStressByTs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssetPrepayAssumption))) :+: (C1 ('MetaCons "PrepaymentPSA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PrepaymentByTerm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[Rate]]))))) |
data AssetDefaultAssumption Source #
stress the default assumption by a factor
Constructors
DefaultConstant Rate | using constant default rate |
DefaultCDR Rate | using annualized default rate |
DefaultVec [Rate] | using default rate vector |
DefaultVecPadding [Rate] | using default rate vector, but padding with last rate till end |
DefaultByAmt (Balance, [Rate]) | |
DefaultAtEnd | default 100% at end |
DefaultAtEndByRate Rate Rate | life time default rate and default rate at end |
DefaultStressByTs Ts AssetDefaultAssumption | |
DefaultByTerm [[Rate]] |
Instances
FromJSON AssetDefaultAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser AssetDefaultAssumption # parseJSONList :: Value -> Parser [AssetDefaultAssumption] # | |||||
ToJSON AssetDefaultAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: AssetDefaultAssumption -> Value # toEncoding :: AssetDefaultAssumption -> Encoding # toJSONList :: [AssetDefaultAssumption] -> Value # toEncodingList :: [AssetDefaultAssumption] -> Encoding # omitField :: AssetDefaultAssumption -> Bool # | |||||
Generic AssetDefaultAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: AssetDefaultAssumption -> Rep AssetDefaultAssumption x # to :: Rep AssetDefaultAssumption x -> AssetDefaultAssumption # | |||||
Read AssetDefaultAssumption Source # | |||||
Defined in Assumptions | |||||
Show AssetDefaultAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> AssetDefaultAssumption -> ShowS # show :: AssetDefaultAssumption -> String # showList :: [AssetDefaultAssumption] -> ShowS # | |||||
type Rep AssetDefaultAssumption Source # | |||||
Defined in Assumptions type Rep AssetDefaultAssumption = D1 ('MetaData "AssetDefaultAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "DefaultConstant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "DefaultCDR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))) :+: (C1 ('MetaCons "DefaultVec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate])) :+: C1 ('MetaCons "DefaultVecPadding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate])))) :+: ((C1 ('MetaCons "DefaultByAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Balance, [Rate]))) :+: C1 ('MetaCons "DefaultAtEnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DefaultAtEndByRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: (C1 ('MetaCons "DefaultStressByTs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssetDefaultAssumption)) :+: C1 ('MetaCons "DefaultByTerm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[Rate]])))))) |
data RecoveryAssumption Source #
Constructors
Recovery (Rate, Int) | recovery rate, recovery lag |
RecoveryTiming (Rate, [Rate]) | recovery rate, with distribution of recoveries |
RecoveryByDays Rate [(Int, Rate)] | recovery rate, with distribution of recoveries by offset dates |
Instances
FromJSON RecoveryAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser RecoveryAssumption # parseJSONList :: Value -> Parser [RecoveryAssumption] # | |||||
ToJSON RecoveryAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: RecoveryAssumption -> Value # toEncoding :: RecoveryAssumption -> Encoding # toJSONList :: [RecoveryAssumption] -> Value # toEncodingList :: [RecoveryAssumption] -> Encoding # omitField :: RecoveryAssumption -> Bool # | |||||
Generic RecoveryAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: RecoveryAssumption -> Rep RecoveryAssumption x # to :: Rep RecoveryAssumption x -> RecoveryAssumption # | |||||
Read RecoveryAssumption Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS RecoveryAssumption # readList :: ReadS [RecoveryAssumption] # | |||||
Show RecoveryAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> RecoveryAssumption -> ShowS # show :: RecoveryAssumption -> String # showList :: [RecoveryAssumption] -> ShowS # | |||||
type Rep RecoveryAssumption Source # | |||||
Defined in Assumptions type Rep RecoveryAssumption = D1 ('MetaData "RecoveryAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Recovery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rate, Int))) :+: (C1 ('MetaCons "RecoveryTiming" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rate, [Rate]))) :+: C1 ('MetaCons "RecoveryByDays" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Rate)])))) |
getRateAssumption :: [RateAssumption] -> Index -> Maybe RateAssumption Source #
projRates :: IRate -> RateType -> Maybe [RateAssumption] -> [Date] -> Either String [IRate] Source #
project rates used by rate type ,with interest rate assumptions and observation dates
Given a list of rates, calcualte whether rates was reset
lookupRate0 :: [RateAssumption] -> Index -> Date -> Either String IRate Source #
data LeaseAssetGapAssump Source #
Constructors
GapDays Int | days between leases, when creating dummy leases |
GapDaysByCurve Ts | days depends on the size of leases, when a default a default days for size greater |
Instances
FromJSON LeaseAssetGapAssump Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser LeaseAssetGapAssump # parseJSONList :: Value -> Parser [LeaseAssetGapAssump] # | |||||
ToJSON LeaseAssetGapAssump Source # | |||||
Defined in Assumptions Methods toJSON :: LeaseAssetGapAssump -> Value # toEncoding :: LeaseAssetGapAssump -> Encoding # toJSONList :: [LeaseAssetGapAssump] -> Value # toEncodingList :: [LeaseAssetGapAssump] -> Encoding # omitField :: LeaseAssetGapAssump -> Bool # | |||||
Generic LeaseAssetGapAssump Source # | |||||
Defined in Assumptions Associated Types
Methods from :: LeaseAssetGapAssump -> Rep LeaseAssetGapAssump x # to :: Rep LeaseAssetGapAssump x -> LeaseAssetGapAssump # | |||||
Read LeaseAssetGapAssump Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS LeaseAssetGapAssump # readList :: ReadS [LeaseAssetGapAssump] # | |||||
Show LeaseAssetGapAssump Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> LeaseAssetGapAssump -> ShowS # show :: LeaseAssetGapAssump -> String # showList :: [LeaseAssetGapAssump] -> ShowS # | |||||
type Rep LeaseAssetGapAssump Source # | |||||
Defined in Assumptions type Rep LeaseAssetGapAssump = D1 ('MetaData "LeaseAssetGapAssump" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "GapDays" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "GapDaysByCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) |
data LeaseAssetRentAssump Source #
Instances
FromJSON LeaseAssetRentAssump Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser LeaseAssetRentAssump # parseJSONList :: Value -> Parser [LeaseAssetRentAssump] # | |||||
ToJSON LeaseAssetRentAssump Source # | |||||
Defined in Assumptions Methods toJSON :: LeaseAssetRentAssump -> Value # toEncoding :: LeaseAssetRentAssump -> Encoding # toJSONList :: [LeaseAssetRentAssump] -> Value # toEncodingList :: [LeaseAssetRentAssump] -> Encoding # omitField :: LeaseAssetRentAssump -> Bool # | |||||
Generic LeaseAssetRentAssump Source # | |||||
Defined in Assumptions Associated Types
Methods from :: LeaseAssetRentAssump -> Rep LeaseAssetRentAssump x # to :: Rep LeaseAssetRentAssump x -> LeaseAssetRentAssump # | |||||
Read LeaseAssetRentAssump Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS LeaseAssetRentAssump # readList :: ReadS [LeaseAssetRentAssump] # | |||||
Show LeaseAssetRentAssump Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> LeaseAssetRentAssump -> ShowS # show :: LeaseAssetRentAssump -> String # showList :: [LeaseAssetRentAssump] -> ShowS # | |||||
type Rep LeaseAssetRentAssump Source # | |||||
Defined in Assumptions type Rep LeaseAssetRentAssump = D1 ('MetaData "LeaseAssetRentAssump" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BaseAnnualRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: (C1 ('MetaCons "BaseCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: C1 ('MetaCons "BaseByVec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate])))) |
data NonPerfAssumption Source #
Constructors
NonPerfAssumption | |
Fields
|
Instances
FromJSON NonPerfAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser NonPerfAssumption # parseJSONList :: Value -> Parser [NonPerfAssumption] # | |||||
ToJSON NonPerfAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: NonPerfAssumption -> Value # toEncoding :: NonPerfAssumption -> Encoding # toJSONList :: [NonPerfAssumption] -> Value # toEncodingList :: [NonPerfAssumption] -> Encoding # omitField :: NonPerfAssumption -> Bool # | |||||
Generic NonPerfAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: NonPerfAssumption -> Rep NonPerfAssumption x # to :: Rep NonPerfAssumption x -> NonPerfAssumption # | |||||
Show NonPerfAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> NonPerfAssumption -> ShowS # show :: NonPerfAssumption -> String # showList :: [NonPerfAssumption] -> ShowS # | |||||
type Rep NonPerfAssumption Source # | |||||
Defined in Assumptions type Rep NonPerfAssumption = D1 ('MetaData "NonPerfAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "NonPerfAssumption" 'PrefixI 'True) (((S1 ('MetaSel ('Just "stopRunBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StopBy)) :*: (S1 ('MetaSel ('Just "projectedExpense") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [(FeeName, Ts)])) :*: S1 ('MetaSel ('Just "callWhen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [CallOpt])))) :*: (S1 ('MetaSel ('Just "revolving") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RevolvingAssumption)) :*: (S1 ('MetaSel ('Just "interest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [RateAssumption])) :*: S1 ('MetaSel ('Just "inspectOn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [InspectType]))))) :*: ((S1 ('MetaSel ('Just "buildFinancialReport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DatePattern)) :*: (S1 ('MetaSel ('Just "pricing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BondPricingInput)) :*: S1 ('MetaSel ('Just "fireTrigger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [(Date, DealCycle, String)])))) :*: (S1 ('MetaSel ('Just "makeWholeWhen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Date, Spread, Table Float Spread))) :*: (S1 ('MetaSel ('Just "issueBondSchedule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TsPoint IssueBondEvent])) :*: S1 ('MetaSel ('Just "refinance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TsPoint RefiEvent]))))))) |
type AssetPerf = (AssetPerfAssumption, AssetDelinqPerfAssumption, AssetDefaultedPerfAssumption) Source #
data AssetDelinquencyAssumption Source #
Constructors
DelinqCDR Rate (Lag, Rate) | Annualized Rate to Delinq status , period lag become defaulted, loss rate, period lag become loss |
DelinqByAmt (Balance, [Rate]) (Lag, Rate) | |
Dummy3 |
Instances
FromJSON AssetDelinquencyAssumption Source # | |||||
Defined in Assumptions | |||||
ToJSON AssetDelinquencyAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: AssetDelinquencyAssumption -> Value # toEncoding :: AssetDelinquencyAssumption -> Encoding # toJSONList :: [AssetDelinquencyAssumption] -> Value # toEncodingList :: [AssetDelinquencyAssumption] -> Encoding # | |||||
Generic AssetDelinquencyAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: AssetDelinquencyAssumption -> Rep AssetDelinquencyAssumption x # to :: Rep AssetDelinquencyAssumption x -> AssetDelinquencyAssumption # | |||||
Read AssetDelinquencyAssumption Source # | |||||
Defined in Assumptions | |||||
Show AssetDelinquencyAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> AssetDelinquencyAssumption -> ShowS # show :: AssetDelinquencyAssumption -> String # showList :: [AssetDelinquencyAssumption] -> ShowS # | |||||
type Rep AssetDelinquencyAssumption Source # | |||||
Defined in Assumptions type Rep AssetDelinquencyAssumption = D1 ('MetaData "AssetDelinquencyAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "DelinqCDR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Lag, Rate))) :+: (C1 ('MetaCons "DelinqByAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Balance, [Rate])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Lag, Rate))) :+: C1 ('MetaCons "Dummy3" 'PrefixI 'False) (U1 :: Type -> Type))) |
data AssetDelinqPerfAssumption Source #
Constructors
DummyDelinqAssump |
Instances
FromJSON AssetDelinqPerfAssumption Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser AssetDelinqPerfAssumption # parseJSONList :: Value -> Parser [AssetDelinqPerfAssumption] # | |||||
ToJSON AssetDelinqPerfAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: AssetDelinqPerfAssumption -> Value # toEncoding :: AssetDelinqPerfAssumption -> Encoding # toJSONList :: [AssetDelinqPerfAssumption] -> Value # | |||||
Generic AssetDelinqPerfAssumption Source # | |||||
Defined in Assumptions Associated Types
Methods from :: AssetDelinqPerfAssumption -> Rep AssetDelinqPerfAssumption x # to :: Rep AssetDelinqPerfAssumption x -> AssetDelinqPerfAssumption # | |||||
Read AssetDelinqPerfAssumption Source # | |||||
Defined in Assumptions | |||||
Show AssetDelinqPerfAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> AssetDelinqPerfAssumption -> ShowS # show :: AssetDelinqPerfAssumption -> String # showList :: [AssetDelinqPerfAssumption] -> ShowS # | |||||
type Rep AssetDelinqPerfAssumption Source # | |||||
data AssetDefaultedPerfAssumption Source #
Constructors
DefaultedRecovery Rate Int [Rate] | |
DummyDefaultAssump |
Instances
FromJSON AssetDefaultedPerfAssumption Source # | |||||
Defined in Assumptions | |||||
ToJSON AssetDefaultedPerfAssumption Source # | |||||
Defined in Assumptions Methods toJSON :: AssetDefaultedPerfAssumption -> Value # toEncoding :: AssetDefaultedPerfAssumption -> Encoding # toJSONList :: [AssetDefaultedPerfAssumption] -> Value # toEncodingList :: [AssetDefaultedPerfAssumption] -> Encoding # | |||||
Generic AssetDefaultedPerfAssumption Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read AssetDefaultedPerfAssumption Source # | |||||
Defined in Assumptions | |||||
Show AssetDefaultedPerfAssumption Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> AssetDefaultedPerfAssumption -> ShowS # show :: AssetDefaultedPerfAssumption -> String # showList :: [AssetDefaultedPerfAssumption] -> ShowS # | |||||
type Rep AssetDefaultedPerfAssumption Source # | |||||
Defined in Assumptions type Rep AssetDefaultedPerfAssumption = D1 ('MetaData "AssetDefaultedPerfAssumption" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "DefaultedRecovery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate]))) :+: C1 ('MetaCons "DummyDefaultAssump" 'PrefixI 'False) (U1 :: Type -> Type)) |
data IssueBondEvent Source #
Constructors
IssueBondEvent (Maybe Pre) BondName AccName Bond (Maybe BalanceFormula) (Maybe RateFormula) | |
FundingBondEvent (Maybe Pre) BondName AccName Balance |
Instances
FromJSON IssueBondEvent Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser IssueBondEvent # parseJSONList :: Value -> Parser [IssueBondEvent] # | |||||
ToJSON IssueBondEvent Source # | |||||
Defined in Assumptions Methods toJSON :: IssueBondEvent -> Value # toEncoding :: IssueBondEvent -> Encoding # toJSONList :: [IssueBondEvent] -> Value # toEncodingList :: [IssueBondEvent] -> Encoding # omitField :: IssueBondEvent -> Bool # | |||||
Generic IssueBondEvent Source # | |||||
Defined in Assumptions Associated Types
Methods from :: IssueBondEvent -> Rep IssueBondEvent x # to :: Rep IssueBondEvent x -> IssueBondEvent # | |||||
Read IssueBondEvent Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS IssueBondEvent # readList :: ReadS [IssueBondEvent] # | |||||
Show IssueBondEvent Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> IssueBondEvent -> ShowS # show :: IssueBondEvent -> String # showList :: [IssueBondEvent] -> ShowS # | |||||
type Rep IssueBondEvent Source # | |||||
Defined in Assumptions |
data TagMatchRule Source #
Constructors
TagEq | match exactly |
TagSubset | match subset |
TagSuperset | match superset |
TagAny | match any tag hit |
TagNot TagMatchRule | Negative match |
Instances
FromJSON TagMatchRule Source # | |||||
Defined in Assumptions | |||||
ToJSON TagMatchRule Source # | |||||
Defined in Assumptions Methods toJSON :: TagMatchRule -> Value # toEncoding :: TagMatchRule -> Encoding # toJSONList :: [TagMatchRule] -> Value # toEncodingList :: [TagMatchRule] -> Encoding # omitField :: TagMatchRule -> Bool # | |||||
Generic TagMatchRule Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read TagMatchRule Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS TagMatchRule # readList :: ReadS [TagMatchRule] # | |||||
Show TagMatchRule Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> TagMatchRule -> ShowS # show :: TagMatchRule -> String # showList :: [TagMatchRule] -> ShowS # | |||||
type Rep TagMatchRule Source # | |||||
Defined in Assumptions type Rep TagMatchRule = D1 ('MetaData "TagMatchRule" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "TagEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TagSubset" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TagSuperset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TagAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TagNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TagMatchRule))))) |
data ObligorStrategy Source #
Constructors
ObligorById [String] AssetPerf | |
ObligorByTag [ObligorTagStr] TagMatchRule AssetPerf | |
ObligorByField [FieldMatchRule] AssetPerf | |
ObligorByDefault AssetPerf |
Instances
FromJSON ObligorStrategy Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser ObligorStrategy # parseJSONList :: Value -> Parser [ObligorStrategy] # | |||||
ToJSON ObligorStrategy Source # | |||||
Defined in Assumptions Methods toJSON :: ObligorStrategy -> Value # toEncoding :: ObligorStrategy -> Encoding # toJSONList :: [ObligorStrategy] -> Value # toEncodingList :: [ObligorStrategy] -> Encoding # omitField :: ObligorStrategy -> Bool # | |||||
Generic ObligorStrategy Source # | |||||
Defined in Assumptions Associated Types
Methods from :: ObligorStrategy -> Rep ObligorStrategy x # to :: Rep ObligorStrategy x -> ObligorStrategy # | |||||
Read ObligorStrategy Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS ObligorStrategy # readList :: ReadS [ObligorStrategy] # | |||||
Show ObligorStrategy Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> ObligorStrategy -> ShowS # show :: ObligorStrategy -> String # showList :: [ObligorStrategy] -> ShowS # | |||||
type Rep ObligorStrategy Source # | |||||
Defined in Assumptions |
Constructors
RefiRate AccountName BondName InterestInfo | |
RefiBond AccountName Bond | |
RefiEvents [RefiEvent] |
Instances
FromJSON RefiEvent Source # | |||||
Defined in Assumptions | |||||
ToJSON RefiEvent Source # | |||||
Generic RefiEvent Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read RefiEvent Source # | |||||
Show RefiEvent Source # | |||||
type Rep RefiEvent Source # | |||||
Defined in Assumptions type Rep RefiEvent = D1 ('MetaData "RefiEvent" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "RefiRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InterestInfo))) :+: (C1 ('MetaCons "RefiBond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bond)) :+: C1 ('MetaCons "RefiEvents" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefiEvent])))) |
data InspectType Source #
Constructors
InspectPt DatePattern DealStats | |
InspectRpt DatePattern [DealStats] |
Instances
FromJSON InspectType Source # | |||||
Defined in Assumptions | |||||
ToJSON InspectType Source # | |||||
Defined in Assumptions Methods toJSON :: InspectType -> Value # toEncoding :: InspectType -> Encoding # toJSONList :: [InspectType] -> Value # toEncodingList :: [InspectType] -> Encoding # omitField :: InspectType -> Bool # | |||||
Generic InspectType Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read InspectType Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS InspectType # readList :: ReadS [InspectType] # readPrec :: ReadPrec InspectType # readListPrec :: ReadPrec [InspectType] # | |||||
Show InspectType Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> InspectType -> ShowS # show :: InspectType -> String # showList :: [InspectType] -> ShowS # | |||||
type Rep InspectType Source # | |||||
Defined in Assumptions type Rep InspectType = D1 ('MetaData "InspectType" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "InspectPt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "InspectRpt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) |
data FieldMatchRule Source #
Constructors
FieldIn String [String] | |
FieldCmp String Cmp Double | |
FieldInRange String RangeType Double Double | |
FieldNot FieldMatchRule |
Instances
FromJSON FieldMatchRule Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser FieldMatchRule # parseJSONList :: Value -> Parser [FieldMatchRule] # | |||||
ToJSON FieldMatchRule Source # | |||||
Defined in Assumptions Methods toJSON :: FieldMatchRule -> Value # toEncoding :: FieldMatchRule -> Encoding # toJSONList :: [FieldMatchRule] -> Value # toEncodingList :: [FieldMatchRule] -> Encoding # omitField :: FieldMatchRule -> Bool # | |||||
Generic FieldMatchRule Source # | |||||
Defined in Assumptions Associated Types
Methods from :: FieldMatchRule -> Rep FieldMatchRule x # to :: Rep FieldMatchRule x -> FieldMatchRule # | |||||
Read FieldMatchRule Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS FieldMatchRule # readList :: ReadS [FieldMatchRule] # | |||||
Show FieldMatchRule Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> FieldMatchRule -> ShowS # show :: FieldMatchRule -> String # showList :: [FieldMatchRule] -> ShowS # | |||||
type Rep FieldMatchRule Source # | |||||
Defined in Assumptions type Rep FieldMatchRule = D1 ('MetaData "FieldMatchRule" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "FieldIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "FieldCmp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) :+: (C1 ('MetaCons "FieldInRange" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :+: C1 ('MetaCons "FieldNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldMatchRule)))) |
Constructors
LegacyOpts [CallOption] | legacy support |
CallPredicate [Pre] | default test call for each pay day, keep backward compatible |
CallOnDates DatePattern [Pre] | test call at end of day |
Instances
FromJSON CallOpt Source # | |||||
Defined in Assumptions | |||||
ToJSON CallOpt Source # | |||||
Generic CallOpt Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read CallOpt Source # | |||||
Show CallOpt Source # | |||||
Eq CallOpt Source # | |||||
Ord CallOpt Source # | |||||
type Rep CallOpt Source # | |||||
Defined in Assumptions type Rep CallOpt = D1 ('MetaData "CallOpt" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "LegacyOpts" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CallOption])) :+: (C1 ('MetaCons "CallPredicate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])) :+: C1 ('MetaCons "CallOnDates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])))) |
_MortgageAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress) Source #
_MortgageDeqAssump :: Prism' AssetPerfAssumption (Maybe AssetDelinquencyAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress) Source #
_LeaseAssump :: Prism' AssetPerfAssumption (Maybe LeaseDefaultType, LeaseAssetGapAssump, LeaseAssetRentAssump, LeaseEndType) Source #
_LoanAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress) Source #
_InstallmentAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe AssetPrepayAssumption, Maybe RecoveryAssumption, Maybe ExtraStress) Source #
_ReceivableAssump :: Prism' AssetPerfAssumption (Maybe AssetDefaultAssumption, Maybe RecoveryAssumption, Maybe ExtraStress) Source #
Instances
FromJSON TradeType Source # | |||||
Defined in Assumptions | |||||
ToJSON TradeType Source # | |||||
Generic TradeType Source # | |||||
Defined in Assumptions Associated Types
| |||||
Show TradeType Source # | |||||
type Rep TradeType Source # | |||||
Defined in Assumptions type Rep TradeType = D1 ('MetaData "TradeType" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "ByCash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "ByBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) |
data LeaseEndType Source #
Instances
FromJSON LeaseEndType Source # | |||||
Defined in Assumptions | |||||
ToJSON LeaseEndType Source # | |||||
Defined in Assumptions Methods toJSON :: LeaseEndType -> Value # toEncoding :: LeaseEndType -> Encoding # toJSONList :: [LeaseEndType] -> Value # toEncodingList :: [LeaseEndType] -> Encoding # omitField :: LeaseEndType -> Bool # | |||||
Generic LeaseEndType Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read LeaseEndType Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS LeaseEndType # readList :: ReadS [LeaseEndType] # | |||||
Show LeaseEndType Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> LeaseEndType -> ShowS # show :: LeaseEndType -> String # showList :: [LeaseEndType] -> ShowS # | |||||
type Rep LeaseEndType Source # | |||||
Defined in Assumptions type Rep LeaseEndType = D1 ('MetaData "LeaseEndType" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "CutByDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "StopByExtTimes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "EarlierOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "LaterOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) |
data LeaseDefaultType Source #
Constructors
DefaultByContinuation Rate | |
DefaultByTermination Rate |
Instances
FromJSON LeaseDefaultType Source # | |||||
Defined in Assumptions Methods parseJSON :: Value -> Parser LeaseDefaultType # parseJSONList :: Value -> Parser [LeaseDefaultType] # | |||||
ToJSON LeaseDefaultType Source # | |||||
Defined in Assumptions Methods toJSON :: LeaseDefaultType -> Value # toEncoding :: LeaseDefaultType -> Encoding # toJSONList :: [LeaseDefaultType] -> Value # toEncodingList :: [LeaseDefaultType] -> Encoding # omitField :: LeaseDefaultType -> Bool # | |||||
Generic LeaseDefaultType Source # | |||||
Defined in Assumptions Associated Types
Methods from :: LeaseDefaultType -> Rep LeaseDefaultType x # to :: Rep LeaseDefaultType x -> LeaseDefaultType # | |||||
Read LeaseDefaultType Source # | |||||
Defined in Assumptions Methods readsPrec :: Int -> ReadS LeaseDefaultType # readList :: ReadS [LeaseDefaultType] # | |||||
Show LeaseDefaultType Source # | |||||
Defined in Assumptions Methods showsPrec :: Int -> LeaseDefaultType -> ShowS # show :: LeaseDefaultType -> String # showList :: [LeaseDefaultType] -> ShowS # | |||||
type Rep LeaseDefaultType Source # | |||||
Defined in Assumptions type Rep LeaseDefaultType = D1 ('MetaData "LeaseDefaultType" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "DefaultByContinuation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "DefaultByTermination" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))) |
Constructors
StopByDate Date | stop by date |
StopByPre DatePattern [Pre] | stop by precondition |
Instances
FromJSON StopBy Source # | |||||
Defined in Assumptions | |||||
ToJSON StopBy Source # | |||||
Generic StopBy Source # | |||||
Defined in Assumptions Associated Types
| |||||
Read StopBy Source # | |||||
Show StopBy Source # | |||||
type Rep StopBy Source # | |||||
Defined in Assumptions type Rep StopBy = D1 ('MetaData "StopBy" "Assumptions" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "StopByDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "StopByPre" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre]))) |