Safe Haskell | None |
---|---|
Language | Haskell2010 |
CreditEnhancement
Synopsis
- data LiqFacility = LiqFacility {
- liqName :: String
- liqType :: LiqSupportType
- liqBalance :: Balance
- liqCredit :: Maybe Balance
- liqCreditCalc :: Maybe LiqCreditCalc
- liqRateType :: Maybe RateType
- liqPremiumRateType :: Maybe RateType
- liqRate :: Maybe IRate
- liqPremiumRate :: Maybe IRate
- liqDueIntDate :: Maybe Date
- liqDueInt :: Balance
- liqDuePremium :: Balance
- liqStart :: Date
- liqEnds :: Maybe Date
- liqStmt :: Maybe Statement
- data LiqSupportType
- buildLiqResetAction :: [LiqFacility] -> Date -> [(String, Dates)] -> [(String, Dates)]
- buildLiqRateResetAction :: [LiqFacility] -> Date -> [(String, Dates)] -> [(String, Dates)]
- type LiquidityProviderName = String
- draw :: Amount -> Date -> LiqFacility -> LiqFacility
- repay :: Amount -> Date -> LiqRepayType -> LiqFacility -> LiqFacility
- accrueLiqProvider :: Date -> LiqFacility -> LiqFacility
- data LiqDrawType
- data LiqRepayType
- data LiqCreditCalc
- consolStmt :: LiqFacility -> LiqFacility
- data CreditDefaultSwap = CDS {
- cdsName :: String
- cdsAccrue :: Maybe DatePattern
- cdsCoverage :: DealStats
- cdsDue :: Balance
- cdsLast :: Maybe Date
- cdsPremiumRefBalance :: DealStats
- cdsPremiumRate :: IRate
- cdsRateType :: RateType
- cdsPremiumDue :: Balance
- cdsLastCalcDate :: Maybe Date
- cdsSettle :: Maybe DatePattern
- cdsSettleDate :: Maybe Date
- cdsNetCash :: Balance
- cdsStart :: Date
- cdsEnds :: Maybe Date
- cdsStmt :: Maybe Statement
Documentation
data LiqFacility Source #
Constructors
LiqFacility | |
Fields
|
Instances
data LiqSupportType Source #
Constructors
ReplenishSupport DatePattern Balance | Credit will be refresh by an interval |
FixSupport Balance | Fixed credit amount |
ByPct DealStats Rate | By a pct of formula |
UnLimit | Unlimit credit support, like insurance company |
Instances
FromJSON LiqSupportType Source # | |||||
Defined in CreditEnhancement Methods parseJSON :: Value -> Parser LiqSupportType # parseJSONList :: Value -> Parser [LiqSupportType] # | |||||
ToJSON LiqSupportType Source # | |||||
Defined in CreditEnhancement Methods toJSON :: LiqSupportType -> Value # toEncoding :: LiqSupportType -> Encoding # toJSONList :: [LiqSupportType] -> Value # toEncodingList :: [LiqSupportType] -> Encoding # omitField :: LiqSupportType -> Bool # | |||||
Generic LiqSupportType Source # | |||||
Defined in CreditEnhancement Associated Types
Methods from :: LiqSupportType -> Rep LiqSupportType x # to :: Rep LiqSupportType x -> LiqSupportType # | |||||
Show LiqSupportType Source # | |||||
Defined in CreditEnhancement Methods showsPrec :: Int -> LiqSupportType -> ShowS # show :: LiqSupportType -> String # showList :: [LiqSupportType] -> ShowS # | |||||
Eq LiqSupportType Source # | |||||
Defined in CreditEnhancement Methods (==) :: LiqSupportType -> LiqSupportType -> Bool # (/=) :: LiqSupportType -> LiqSupportType -> Bool # | |||||
Ord LiqSupportType Source # | |||||
Defined in CreditEnhancement Methods compare :: LiqSupportType -> LiqSupportType -> Ordering # (<) :: LiqSupportType -> LiqSupportType -> Bool # (<=) :: LiqSupportType -> LiqSupportType -> Bool # (>) :: LiqSupportType -> LiqSupportType -> Bool # (>=) :: LiqSupportType -> LiqSupportType -> Bool # max :: LiqSupportType -> LiqSupportType -> LiqSupportType # min :: LiqSupportType -> LiqSupportType -> LiqSupportType # | |||||
type Rep LiqSupportType Source # | |||||
Defined in CreditEnhancement type Rep LiqSupportType = D1 ('MetaData "LiqSupportType" "CreditEnhancement" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "ReplenishSupport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "FixSupport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: (C1 ('MetaCons "ByPct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "UnLimit" 'PrefixI 'False) (U1 :: Type -> Type))) |
buildLiqResetAction :: [LiqFacility] -> Date -> [(String, Dates)] -> [(String, Dates)] Source #
update the reset events of liquidity provider
buildLiqRateResetAction :: [LiqFacility] -> Date -> [(String, Dates)] -> [(String, Dates)] Source #
update the rate reset events of liquidity provider
type LiquidityProviderName = String Source #
describle credit support
draw :: Amount -> Date -> LiqFacility -> LiqFacility Source #
draw cash from liquidity provider
repay :: Amount -> Date -> LiqRepayType -> LiqFacility -> LiqFacility Source #
accrueLiqProvider :: Date -> LiqFacility -> LiqFacility Source #
accure fee and interest of a liquidity provider and update credit available
data LiqDrawType Source #
Constructors
LiqToAcc | draw credit and deposit cash to account |
LiqToBondInt | draw credit and pay to bond interest if any shortfall |
LiqToBondPrin | draw credit and pay to bond principal if any shortfall |
LiqToFee | draw credit and pay to a fee if there is a shortfall |
Instances
FromJSON LiqDrawType Source # | |||||
Defined in CreditEnhancement | |||||
ToJSON LiqDrawType Source # | |||||
Defined in CreditEnhancement Methods toJSON :: LiqDrawType -> Value # toEncoding :: LiqDrawType -> Encoding # toJSONList :: [LiqDrawType] -> Value # toEncodingList :: [LiqDrawType] -> Encoding # omitField :: LiqDrawType -> Bool # | |||||
Generic LiqDrawType Source # | |||||
Defined in CreditEnhancement Associated Types
| |||||
Show LiqDrawType Source # | |||||
Defined in CreditEnhancement Methods showsPrec :: Int -> LiqDrawType -> ShowS # show :: LiqDrawType -> String # showList :: [LiqDrawType] -> ShowS # | |||||
Eq LiqDrawType Source # | |||||
Defined in CreditEnhancement | |||||
Ord LiqDrawType Source # | |||||
Defined in CreditEnhancement Methods compare :: LiqDrawType -> LiqDrawType -> Ordering # (<) :: LiqDrawType -> LiqDrawType -> Bool # (<=) :: LiqDrawType -> LiqDrawType -> Bool # (>) :: LiqDrawType -> LiqDrawType -> Bool # (>=) :: LiqDrawType -> LiqDrawType -> Bool # max :: LiqDrawType -> LiqDrawType -> LiqDrawType # min :: LiqDrawType -> LiqDrawType -> LiqDrawType # | |||||
type Rep LiqDrawType Source # | |||||
Defined in CreditEnhancement type Rep LiqDrawType = D1 ('MetaData "LiqDrawType" "CreditEnhancement" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "LiqToAcc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiqToBondInt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LiqToBondPrin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiqToFee" 'PrefixI 'False) (U1 :: Type -> Type))) |
data LiqRepayType Source #
Constructors
LiqBal | repay oustanding balance of liquidation provider |
LiqPremium | repay oustanding premium fee of lp |
LiqInt | repay oustanding interest of lp |
LiqRepayTypes [LiqRepayType] | repay by sequence |
LiqResidual | |
LiqOD |
Instances
FromJSON LiqRepayType Source # | |||||
Defined in CreditEnhancement | |||||
ToJSON LiqRepayType Source # | |||||
Defined in CreditEnhancement Methods toJSON :: LiqRepayType -> Value # toEncoding :: LiqRepayType -> Encoding # toJSONList :: [LiqRepayType] -> Value # toEncodingList :: [LiqRepayType] -> Encoding # omitField :: LiqRepayType -> Bool # | |||||
Generic LiqRepayType Source # | |||||
Defined in CreditEnhancement Associated Types
| |||||
Show LiqRepayType Source # | |||||
Defined in CreditEnhancement Methods showsPrec :: Int -> LiqRepayType -> ShowS # show :: LiqRepayType -> String # showList :: [LiqRepayType] -> ShowS # | |||||
Eq LiqRepayType Source # | |||||
Defined in CreditEnhancement | |||||
Ord LiqRepayType Source # | |||||
Defined in CreditEnhancement Methods compare :: LiqRepayType -> LiqRepayType -> Ordering # (<) :: LiqRepayType -> LiqRepayType -> Bool # (<=) :: LiqRepayType -> LiqRepayType -> Bool # (>) :: LiqRepayType -> LiqRepayType -> Bool # (>=) :: LiqRepayType -> LiqRepayType -> Bool # max :: LiqRepayType -> LiqRepayType -> LiqRepayType # min :: LiqRepayType -> LiqRepayType -> LiqRepayType # | |||||
type Rep LiqRepayType Source # | |||||
Defined in CreditEnhancement type Rep LiqRepayType = D1 ('MetaData "LiqRepayType" "CreditEnhancement" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "LiqBal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LiqPremium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiqInt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LiqRepayTypes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LiqRepayType])) :+: (C1 ('MetaCons "LiqResidual" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiqOD" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data LiqCreditCalc Source #
Constructors
IncludeDueInt | |
IncludeDuePremium | |
IncludeBoth |
Instances
FromJSON LiqCreditCalc Source # | |||||
Defined in CreditEnhancement Methods parseJSON :: Value -> Parser LiqCreditCalc # parseJSONList :: Value -> Parser [LiqCreditCalc] # | |||||
ToJSON LiqCreditCalc Source # | |||||
Defined in CreditEnhancement Methods toJSON :: LiqCreditCalc -> Value # toEncoding :: LiqCreditCalc -> Encoding # toJSONList :: [LiqCreditCalc] -> Value # toEncodingList :: [LiqCreditCalc] -> Encoding # omitField :: LiqCreditCalc -> Bool # | |||||
Generic LiqCreditCalc Source # | |||||
Defined in CreditEnhancement Associated Types
| |||||
Show LiqCreditCalc Source # | |||||
Defined in CreditEnhancement Methods showsPrec :: Int -> LiqCreditCalc -> ShowS # show :: LiqCreditCalc -> String # showList :: [LiqCreditCalc] -> ShowS # | |||||
Eq LiqCreditCalc Source # | |||||
Defined in CreditEnhancement Methods (==) :: LiqCreditCalc -> LiqCreditCalc -> Bool # (/=) :: LiqCreditCalc -> LiqCreditCalc -> Bool # | |||||
Ord LiqCreditCalc Source # | |||||
Defined in CreditEnhancement Methods compare :: LiqCreditCalc -> LiqCreditCalc -> Ordering # (<) :: LiqCreditCalc -> LiqCreditCalc -> Bool # (<=) :: LiqCreditCalc -> LiqCreditCalc -> Bool # (>) :: LiqCreditCalc -> LiqCreditCalc -> Bool # (>=) :: LiqCreditCalc -> LiqCreditCalc -> Bool # max :: LiqCreditCalc -> LiqCreditCalc -> LiqCreditCalc # min :: LiqCreditCalc -> LiqCreditCalc -> LiqCreditCalc # | |||||
type Rep LiqCreditCalc Source # | |||||
Defined in CreditEnhancement type Rep LiqCreditCalc = D1 ('MetaData "LiqCreditCalc" "CreditEnhancement" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "IncludeDueInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IncludeDuePremium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IncludeBoth" 'PrefixI 'False) (U1 :: Type -> Type))) |
consolStmt :: LiqFacility -> LiqFacility Source #
data CreditDefaultSwap Source #
Constructors
CDS | |
Fields
|
Instances
UseRate CreditDefaultSwap Source # | |||||
Defined in CreditEnhancement Methods isAdjustbleRate :: CreditDefaultSwap -> Bool Source # getIndex :: CreditDefaultSwap -> Maybe Index Source # getIndexes :: CreditDefaultSwap -> Maybe [Index] Source # | |||||
Generic CreditDefaultSwap Source # | |||||
Defined in CreditEnhancement Associated Types
Methods from :: CreditDefaultSwap -> Rep CreditDefaultSwap x # to :: Rep CreditDefaultSwap x -> CreditDefaultSwap # | |||||
Show CreditDefaultSwap Source # | |||||
Defined in CreditEnhancement Methods showsPrec :: Int -> CreditDefaultSwap -> ShowS # show :: CreditDefaultSwap -> String # showList :: [CreditDefaultSwap] -> ShowS # | |||||
Eq CreditDefaultSwap Source # | |||||
Defined in CreditEnhancement Methods (==) :: CreditDefaultSwap -> CreditDefaultSwap -> Bool # (/=) :: CreditDefaultSwap -> CreditDefaultSwap -> Bool # | |||||
Ord CreditDefaultSwap Source # | |||||
Defined in CreditEnhancement Methods compare :: CreditDefaultSwap -> CreditDefaultSwap -> Ordering # (<) :: CreditDefaultSwap -> CreditDefaultSwap -> Bool # (<=) :: CreditDefaultSwap -> CreditDefaultSwap -> Bool # (>) :: CreditDefaultSwap -> CreditDefaultSwap -> Bool # (>=) :: CreditDefaultSwap -> CreditDefaultSwap -> Bool # max :: CreditDefaultSwap -> CreditDefaultSwap -> CreditDefaultSwap # min :: CreditDefaultSwap -> CreditDefaultSwap -> CreditDefaultSwap # | |||||
type Rep CreditDefaultSwap Source # | |||||
Defined in CreditEnhancement type Rep CreditDefaultSwap = D1 ('MetaData "CreditDefaultSwap" "CreditEnhancement" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "CDS" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "cdsName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "cdsAccrue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DatePattern))) :*: (S1 ('MetaSel ('Just "cdsCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Just "cdsDue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Just "cdsLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)) :*: S1 ('MetaSel ('Just "cdsPremiumRefBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Just "cdsPremiumRate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Just "cdsRateType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RateType)))) :*: (((S1 ('MetaSel ('Just "cdsPremiumDue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Just "cdsLastCalcDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date))) :*: (S1 ('MetaSel ('Just "cdsSettle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DatePattern)) :*: S1 ('MetaSel ('Just "cdsSettleDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)))) :*: ((S1 ('MetaSel ('Just "cdsNetCash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Just "cdsStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :*: (S1 ('MetaSel ('Just "cdsEnds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)) :*: S1 ('MetaSel ('Just "cdsStmt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Statement))))))) |