| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Types
Contents
Synopsis
- data DayCount
- data DateType
- data DatePattern
- = MonthEnd
- | QuarterEnd
- | YearEnd
- | MonthFirst
- | QuarterFirst
- | MidYear
- | YearFirst
- | MonthDayOfYear Int Int
- | DayOfMonth Int
- | SemiAnnual (Int, Int) (Int, Int)
- | CustomDate [Date]
- | SingletonDate Date
- | DaysInYear [(Int, Int)]
- | EveryNMonth Date Int
- | Weekday Int
- | AllDatePattern [DatePattern]
- | StartsExclusive Date DatePattern
- | StartsAt CutoffType Date DatePattern
- | EndsAt CutoffType Date DatePattern
- | Exclude DatePattern [DatePattern]
- | OffsetBy DatePattern Int
- type BondName = String
- type BondNames = [String]
- type FeeName = String
- type FeeNames = [String]
- type AccName = String
- type AccNames = [String]
- type AccountName = String
- data Ts
- = FloatCurve [TsPoint Rational]
- | BoolCurve [TsPoint Bool]
- | BalanceCurve [TsPoint Balance]
- | LeftBalanceCurve [TsPoint Balance]
- | RatioCurve [TsPoint Rational]
- | ThresholdCurve [TsPoint Rational]
- | IRateCurve [TsPoint IRate]
- | FactorCurveClosed [TsPoint Rational] Date
- | PricingCurve [TsPoint Rational]
- | PeriodCurve [TsPoint Int]
- | IntCurve [TsPoint Int]
- data TsPoint a = TsPoint Date a
- data PoolSource
- data PerPoint a = PerPoint Int a
- data PerCurve a
- = CurrentVal [PerPoint a]
- | WithTrailVal [PerPoint a]
- getValFromPerCurve :: PerCurve a -> DateDirection -> CutoffType -> Int -> Maybe a
- data Period
- data Threshold
- data RangeType
- data CutoffType
- data DealStatus
- type Balance = Centi
- data Index
- data Cmp
- data TimeHorizion
- type Date = Day
- type Dates = [Day]
- class TimeSeries ts where
- cmp :: ts -> ts -> Ordering
- sameDate :: ts -> ts -> Bool
- getDate :: ts -> Date
- getDates :: [ts] -> [Date]
- filterByDate :: [ts] -> Date -> [ts]
- sliceBy :: RangeType -> StartDate -> EndDate -> [ts] -> [ts]
- cutBy :: CutoffType -> DateDirection -> Date -> [ts] -> [ts]
- cmpWith :: ts -> Date -> Ordering
- isAfter :: ts -> Date -> Bool
- isOnAfter :: ts -> Date -> Bool
- isBefore :: ts -> Date -> Bool
- isOnBefore :: ts -> Date -> Bool
- splitBy :: Date -> CutoffType -> [ts] -> ([ts], [ts])
- getByDate :: Date -> [ts] -> Maybe ts
- type IRate = Micro
- type Amount = Balance
- type Rate = Rational
- type StartDate = Date
- type EndDate = Date
- type Lag = Int
- type Spread = Micro
- type Floor = Micro
- type Cap = Micro
- type Interest = Balance
- type Principal = Balance
- type Cash = Balance
- type Default = Balance
- type Loss = Balance
- type Rental = Balance
- type PrepaymentPenalty = Balance
- data SplitType
- data BookItem
- type BookItems = [BookItem]
- data BalanceSheetReport = BalanceSheetReport {}
- data CashflowReport = CashflowReport {}
- type Floater = (Index, Spread)
- type CeName = String
- data RateAssumption
- type PrepaymentRate = Rate
- type DefaultRate = Rate
- type RecoveryRate = Rate
- type RemainTerms = Int
- type Recovery = Balance
- type Prepayment = Balance
- data Table a b = ThresholdTable [(a, b)]
- lookupTable :: Ord a => Table a b -> Direction -> (a -> Bool) -> Maybe b
- data Direction
- epocDate :: Day
- type BorrowerNum = Int
- data Txn
- = BondTxn Date Balance Interest Principal IRate Cash DueInt DueIoI (Maybe Float) TxnComment
- | AccTxn Date Balance Amount TxnComment
- | ExpTxn Date Balance Amount Balance TxnComment
- | SupportTxn Date (Maybe Balance) Balance DueInt DuePremium Cash TxnComment
- | IrsTxn Date Balance Amount IRate IRate Balance TxnComment
- | EntryTxn Date Balance Amount TxnComment
- | TrgTxn Date Bool TxnComment
- data TxnComment
- = PayInt [BondName]
- | PayYield BondName
- | PayPrin [BondName]
- | PayGroupPrin [BondName]
- | PayGroupInt [BondName]
- | WriteOff BondName Balance
- | FundWith BondName Balance
- | PayPrinResidual [BondName]
- | PayFee FeeName
- | SeqPayFee [FeeName]
- | PayFeeYield FeeName
- | Transfer AccName AccName
- | TransferBy AccName AccName Limit
- | BookLedgerBy BookDirection String
- | PoolInflow (Maybe [PoolId]) PoolSource
- | LiquidationProceeds [PoolId]
- | LiquidationSupport String
- | LiquidationDraw
- | LiquidationRepay String
- | LiquidationSupportInt Balance Balance
- | BankInt
- | SupportDraw
- | Empty
- | Tag String
- | UsingDS DealStats
- | SwapAccrue
- | SwapInSettle String
- | SwapOutSettle String
- | PurchaseAsset String Balance
- | IssuanceProceeds String
- | TxnDirection BookDirection
- | TxnComments [TxnComment]
- data RoundingBy a
- = RoundCeil a
- | RoundFloor a
- data DateDirection
- data BookDirection
- type IRR = Micro
- data DealCycle
- data Limit
- data Pre
- = IfZero DealStats
- | If Cmp DealStats Balance
- | IfRate Cmp DealStats Micro
- | IfCurve Cmp DealStats Ts
- | IfByPeriodCurve Cmp DealStats DealStats (PerCurve Balance)
- | IfRateCurve Cmp DealStats Ts
- | IfRateByPeriodCurve Cmp DealStats DealStats (PerCurve Rate)
- | IfIntCurve Cmp DealStats Ts
- | IfInt Cmp DealStats Int
- | IfIntBetween DealStats RangeType Int Int
- | IfIntIn DealStats [Int]
- | IfDate Cmp Date
- | IfDateBetween RangeType Date Date
- | IfDateIn Dates
- | IfBool DealStats Bool
- | If2 Cmp DealStats DealStats
- | IfRate2 Cmp DealStats DealStats
- | IfInt2 Cmp DealStats DealStats
- | IfDealStatus DealStatus
- | Always Bool
- | IfNot Pre
- | Any [Pre]
- | All [Pre]
- class Liable lb where
- isPaidOff :: lb -> Bool
- getCurBalance :: lb -> Balance
- getCurRate :: lb -> IRate
- getOriginBalance :: lb -> Balance
- getOriginDate :: lb -> Date
- getAccrueBegDate :: lb -> Date
- getDueInt :: lb -> Balance
- getDueIntAt :: lb -> Int -> Balance
- getDueIntOverInt :: lb -> Balance
- getDueIntOverIntAt :: lb -> Int -> Balance
- getTotalDueInt :: lb -> Balance
- getTotalDueIntAt :: lb -> Int -> Balance
- getOutstandingAmount :: lb -> Balance
- type CumPrepay = Balance
- type CumDefault = Balance
- type CumDelinq = Balance
- type CumPrincipal = Balance
- type CumLoss = Balance
- type CumRecovery = Balance
- data PoolId
- type DealName = String
- lookupIntervalTable :: Ord a => Table a b -> Direction -> (a -> Bool) -> Maybe ((a, b), (a, b))
- data CutoffFields
- data PriceResult
- = PriceResult Valuation PerFace WAL Duration Convexity AccruedInterest [Txn]
- | AssetPrice Valuation WAL Duration Convexity AccruedInterest
- | OASResult PriceResult [Valuation] Spread
- | ZSpread Spread
- | IrrResult IRR [Txn]
- type DueInt = Balance
- type DuePremium = Balance
- type DueIoI = Balance
- type DateVector = (Date, DatePattern)
- data DealStats
- = CurrentBondBalance
- | CurrentPoolBalance (Maybe [PoolId])
- | CurrentPoolBegBalance (Maybe [PoolId])
- | CurrentPoolDefaultedBalance
- | CumulativePoolDefaultedBalance (Maybe [PoolId])
- | CumulativePoolRecoveriesBalance (Maybe [PoolId])
- | CumulativeNetLoss (Maybe [PoolId])
- | OriginalBondBalance
- | OriginalBondBalanceOf [BondName]
- | BondTotalFunding [BondName]
- | OriginalPoolBalance (Maybe [PoolId])
- | DealIssuanceBalance (Maybe [PoolId])
- | UseCustomData String
- | PoolCumCollection [PoolSource] (Maybe [PoolId])
- | PoolCumCollectionTill Int [PoolSource] (Maybe [PoolId])
- | PoolCurCollection [PoolSource] (Maybe [PoolId])
- | PoolCollectionStats Int [PoolSource] (Maybe [PoolId])
- | PoolWaSpread (Maybe [PoolId])
- | AllAccBalance
- | AccBalance [AccName]
- | LedgerBalance [String]
- | LedgerBalanceBy BookDirection [String]
- | LedgerTxnAmt [String] (Maybe TxnComment)
- | ReserveBalance [AccName]
- | ReserveGap [AccName]
- | ReserveExcess [AccName]
- | ReserveGapAt Date [AccName]
- | ReserveExcessAt Date [AccName]
- | FutureCurrentPoolBalance (Maybe [PoolId])
- | FutureCurrentSchedulePoolBalance (Maybe [PoolId])
- | FutureCurrentSchedulePoolBegBalance (Maybe [PoolId])
- | PoolScheduleCfPv PricingMethod (Maybe [PoolId])
- | FuturePoolScheduleCfPv Date PricingMethod (Maybe [PoolId])
- | FutureWaCurrentPoolBalance Date Date (Maybe [PoolId])
- | FutureCurrentPoolBegBalance (Maybe [PoolId])
- | FutureCurrentBondBalance Date
- | CurrentBondBalanceOf [BondName]
- | BondIntPaidAt Date BondName
- | BondsIntPaidAt Date [BondName]
- | BondPrinPaidAt Date BondName
- | BondsPrinPaidAt Date [BondName]
- | BondBalanceTarget [BondName]
- | BondBalanceGap BondName
- | BondBalanceGapAt Date BondName
- | BondDuePrin [BondName]
- | BondReturn BondName Balance [TsPoint Amount]
- | FeePaidAmt [FeeName]
- | FeeTxnAmt [FeeName] (Maybe TxnComment)
- | BondTxnAmt [BondName] (Maybe TxnComment)
- | AccTxnAmt [AccName] (Maybe TxnComment)
- | FeeTxnAmtBy Date [FeeName] (Maybe TxnComment)
- | BondTxnAmtBy Date [BondName] (Maybe TxnComment)
- | AccTxnAmtBy Date [AccName] (Maybe TxnComment)
- | FeesPaidAt Date [FeeName]
- | CurrentDueBondInt [BondName]
- | CurrentDueBondIntAt Int [BondName]
- | CurrentDueBondIntOverInt [BondName]
- | CurrentDueBondIntOverIntAt Int [BondName]
- | CurrentDueBondIntTotal [BondName]
- | CurrentDueBondIntTotalAt Int [BondName]
- | CurrentDueFee [FeeName]
- | LastBondIntPaid [BondName]
- | LastBondPrinPaid [BondName]
- | LastFeePaid [FeeName]
- | LiqCredit [String]
- | LiqBalance [String]
- | RateCapNet String
- | RateSwapNet String
- | BondBalanceHistory Date Date
- | PoolCollectionHistory PoolSource Date Date (Maybe [PoolId])
- | UnderlyingBondBalance (Maybe [BondName])
- | WeightedAvgCurrentPoolBalance Date Date (Maybe [PoolId])
- | WeightedAvgCurrentBondBalance Date Date [BondName]
- | WeightedAvgOriginalPoolBalance Date Date (Maybe [PoolId])
- | WeightedAvgOriginalBondBalance Date Date [BondName]
- | CustomData String Date
- | DealStatBalance DealStatFields
- | AmountRequiredForTargetIRR Double BondName
- | CurrentPoolBorrowerNum (Maybe [PoolId])
- | FutureCurrentPoolBorrowerNum Date (Maybe [PoolId])
- | ProjCollectPeriodNum
- | MonthsTillMaturity BondName
- | DealStatInt DealStatFields
- | TestRate DealStats Cmp Micro
- | TestAny Bool [DealStats]
- | TestAll Bool [DealStats]
- | TestNot DealStats
- | IsDealStatus DealStatus
- | IsMostSenior BondName [BondName]
- | IsPaidOff [BondName]
- | IsFeePaidOff [String]
- | IsLiqSupportPaidOff [String]
- | IsRateSwapPaidOff [String]
- | IsOutstanding [BondName]
- | HasPassedMaturity [BondName]
- | TriggersStatus DealCycle String
- | DealStatBool DealStatFields
- | PoolWaRate (Maybe PoolId)
- | BondRate BondName
- | CumulativeNetLossRatio (Maybe [PoolId])
- | FutureCurrentBondFactor Date
- | FutureCurrentPoolFactor Date (Maybe [PoolId])
- | BondFactor
- | BondFactorOf BondName
- | CumulativePoolDefaultedRate (Maybe [PoolId])
- | CumulativePoolDefaultedRateTill Int (Maybe [PoolId])
- | PoolFactor (Maybe [PoolId])
- | BondWaRate [BondName]
- | DealStatRate DealStatFields
- | Factor DealStats Rational
- | Multiply [DealStats]
- | Max [DealStats]
- | Min [DealStats]
- | Sum [DealStats]
- | Substract [DealStats]
- | Subtract [DealStats]
- | Excess [DealStats]
- | Avg [DealStats]
- | AvgRatio [DealStats]
- | Divide DealStats DealStats
- | DivideRatio DealStats DealStats
- | Constant Rational
- | FloorAndCap DealStats DealStats DealStats
- | FloorWith DealStats DealStats
- | FloorWithZero DealStats
- | CapWith DealStats DealStats
- | Abs DealStats
- | Round DealStats (RoundingBy Rational)
- data PricingMethod
- data CustomDataType
- data ResultComponent
- = CallAt Date
- | DealStatusChangeTo Date DealStatus DealStatus String
- | BondOutstanding String Balance Balance
- | BondOutstandingInt String Balance Balance
- | InspectBal Date DealStats Balance
- | InspectInt Date DealStats Int
- | InspectRate Date DealStats Micro
- | InspectBool Date DealStats Bool
- | RunningWaterfall Date ActionWhen
- | FinancialReport StartDate EndDate BalanceSheetReport CashflowReport
- | InspectWaterfall Date (Maybe String) [DealStats] [String]
- | ErrorMsg String
- | WarningMsg String
- | EndRun (Maybe Date) String
- data DealStatType
- = RtnBalance
- | RtnRate
- | RtnBool
- | RtnInt
- data ActionWhen
- data DealStatFields
- getDealStatType :: DealStats -> DealStatType
- getPriceValue :: PriceResult -> Balance
- preHasTrigger :: Pre -> [(DealCycle, String)]
- data MyRatio
- data HowToPay
- data BondPricingMethod
- data InvestorAction
- _BondTxn :: Prism' Txn (Date, Balance, Interest, Principal, IRate, Cash, DueInt, DueIoI, Maybe Float, TxnComment)
- _InspectBal :: Prism' ResultComponent (Date, DealStats, Balance)
- _IrrResult :: Prism' PriceResult (IRR, [Txn])
Documentation
Constructors
| DC_30E_360 | ISMA European 30S/360 Special German Eurobond Basis |
| DC_30Ep_360 | 30E+/360 |
| DC_ACT_360 | Actual/360 , French |
| DC_ACT_365 | |
| DC_ACT_365A | Actual/365 Actual |
| DC_ACT_365L | Actual/365 Leap Year |
| DC_NL_365 | Actual/365 No leap year |
| DC_ACT_365F | Actual /365 Fixed, English |
| DC_ACT_ACT | Actual/Actual ISDA |
| DC_30_360_ISDA | IDSA |
| DC_30_360_German | Gernman |
| DC_30_360_US | 30/360 US Municipal , Bond basis |
Instances
| FromJSON DayCount Source # | |||||
| ToJSON DayCount Source # | |||||
| Generic DayCount Source # | |||||
Defined in Types Associated Types
| |||||
| Read DayCount Source # | |||||
| Show DayCount Source # | |||||
| Eq DayCount Source # | |||||
| Ord DayCount Source # | |||||
Defined in Types | |||||
| ToSchema DayCount Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy DayCount -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep DayCount Source # | |||||
Defined in Types type Rep DayCount = D1 ('MetaData "DayCount" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "DC_30E_360" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_30Ep_360" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_360" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DC_ACT_365" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_ACT_365A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_365L" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DC_NL_365" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_ACT_365F" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_ACT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DC_30_360_ISDA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_30_360_German" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_30_360_US" 'PrefixI 'False) (U1 :: Type -> Type))))) | |||||
Constructors
| ClosingDate | deal closing day |
| CutoffDate | after which, the pool cashflow was aggregated to SPV |
| FirstPayDate | first payment day for bond/waterfall to run with |
| NextPayDate | |
| NextCollectDate | |
| FirstCollectDate | first collection day for pool |
| LastCollectDate | last collection day for pool |
| LastPayDate | last payment day for bond/waterfall |
| StatedMaturityDate | sated maturity date, all cashflow projection/deal action stops by |
| DistributionDates | distribution date for waterfall |
| CollectionDates | collection date for pool |
| CustomExeDates String | custom execution date |
Instances
data DatePattern Source #
Constructors
| MonthEnd | |
| QuarterEnd | |
| YearEnd | |
| MonthFirst | |
| QuarterFirst | |
| MidYear | |
| YearFirst | |
| MonthDayOfYear Int Int | |
| DayOfMonth Int | |
| SemiAnnual (Int, Int) (Int, Int) | |
| CustomDate [Date] | |
| SingletonDate Date | |
| DaysInYear [(Int, Int)] | |
| EveryNMonth Date Int | |
| Weekday Int | |
| AllDatePattern [DatePattern] | |
| StartsExclusive Date DatePattern | |
| StartsAt CutoffType Date DatePattern | |
| EndsAt CutoffType Date DatePattern | |
| Exclude DatePattern [DatePattern] | |
| OffsetBy DatePattern Int |
Instances
| FromJSON DatePattern Source # | |||||
Defined in Types | |||||
| ToJSON DatePattern Source # | |||||
Defined in Types Methods toJSON :: DatePattern -> Value # toEncoding :: DatePattern -> Encoding # toJSONList :: [DatePattern] -> Value # toEncodingList :: [DatePattern] -> Encoding # omitField :: DatePattern -> Bool # | |||||
| Generic DatePattern Source # | |||||
Defined in Types Associated Types
| |||||
| Read DatePattern Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS DatePattern # readList :: ReadS [DatePattern] # readPrec :: ReadPrec DatePattern # readListPrec :: ReadPrec [DatePattern] # | |||||
| Show DatePattern Source # | DayOfWeek Int -- T.DayOfWeek | ||||
Defined in Types Methods showsPrec :: Int -> DatePattern -> ShowS # show :: DatePattern -> String # showList :: [DatePattern] -> ShowS # | |||||
| Eq DatePattern Source # | |||||
Defined in Types | |||||
| Ord DatePattern Source # | |||||
Defined in Types Methods compare :: DatePattern -> DatePattern -> Ordering # (<) :: DatePattern -> DatePattern -> Bool # (<=) :: DatePattern -> DatePattern -> Bool # (>) :: DatePattern -> DatePattern -> Bool # (>=) :: DatePattern -> DatePattern -> Bool # max :: DatePattern -> DatePattern -> DatePattern # min :: DatePattern -> DatePattern -> DatePattern # | |||||
| ToSchema DatePattern Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy DatePattern -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep DatePattern Source # | |||||
Defined in Types type Rep DatePattern = D1 ('MetaData "DatePattern" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "MonthEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuarterEnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "YearEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonthFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuarterFirst" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MidYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "YearFirst" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonthDayOfYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "DayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "SemiAnnual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int))))))) :+: (((C1 ('MetaCons "CustomDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Date])) :+: C1 ('MetaCons "SingletonDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))) :+: (C1 ('MetaCons "DaysInYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Int)])) :+: (C1 ('MetaCons "EveryNMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Weekday" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "AllDatePattern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DatePattern])) :+: (C1 ('MetaCons "StartsExclusive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern)) :+: C1 ('MetaCons "StartsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CutoffType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))))) :+: (C1 ('MetaCons "EndsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CutoffType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))) :+: (C1 ('MetaCons "Exclude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DatePattern])) :+: C1 ('MetaCons "OffsetBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))) | |||||
type AccountName = String Source #
Constructors
| FloatCurve [TsPoint Rational] | |
| BoolCurve [TsPoint Bool] | |
| BalanceCurve [TsPoint Balance] | |
| LeftBalanceCurve [TsPoint Balance] | |
| RatioCurve [TsPoint Rational] | |
| ThresholdCurve [TsPoint Rational] | |
| IRateCurve [TsPoint IRate] | |
| FactorCurveClosed [TsPoint Rational] Date | |
| PricingCurve [TsPoint Rational] | |
| PeriodCurve [TsPoint Int] | |
| IntCurve [TsPoint Int] |
Instances
| FromJSON Ts Source # | |||||
| ToJSON Ts Source # | |||||
| Generic Ts Source # | |||||
Defined in Types Associated Types
| |||||
| Read Ts Source # | |||||
| Show Ts Source # | |||||
| Eq Ts Source # | |||||
| Ord Ts Source # | |||||
| ToSchema Ts Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Ts -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep Ts Source # | |||||
Defined in Types type Rep Ts = D1 ('MetaData "Ts" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "FloatCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: C1 ('MetaCons "BoolCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Bool]))) :+: (C1 ('MetaCons "BalanceCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Balance])) :+: (C1 ('MetaCons "LeftBalanceCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Balance])) :+: C1 ('MetaCons "RatioCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational]))))) :+: ((C1 ('MetaCons "ThresholdCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: (C1 ('MetaCons "IRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint IRate])) :+: C1 ('MetaCons "FactorCurveClosed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: (C1 ('MetaCons "PricingCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: (C1 ('MetaCons "PeriodCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Int])) :+: C1 ('MetaCons "IntCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Int])))))) | |||||
Instances
| TimeSeries (TsPoint a) Source # | |||||
Defined in Types Methods cmp :: TsPoint a -> TsPoint a -> Ordering Source # sameDate :: TsPoint a -> TsPoint a -> Bool Source # getDate :: TsPoint a -> Date Source # getDates :: [TsPoint a] -> [Date] Source # filterByDate :: [TsPoint a] -> Date -> [TsPoint a] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [TsPoint a] -> [TsPoint a] Source # cutBy :: CutoffType -> DateDirection -> Date -> [TsPoint a] -> [TsPoint a] Source # cmpWith :: TsPoint a -> Date -> Ordering Source # isAfter :: TsPoint a -> Date -> Bool Source # isOnAfter :: TsPoint a -> Date -> Bool Source # isBefore :: TsPoint a -> Date -> Bool Source # isOnBefore :: TsPoint a -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [TsPoint a] -> ([TsPoint a], [TsPoint a]) Source # getByDate :: Date -> [TsPoint a] -> Maybe (TsPoint a) Source # | |||||
| FromJSON a => FromJSON (TsPoint a) Source # | |||||
| ToJSON a => ToJSON (TsPoint a) Source # | |||||
| Generic (TsPoint a) Source # | |||||
Defined in Types Associated Types
| |||||
| Read a => Read (TsPoint a) Source # | |||||
| Show a => Show (TsPoint a) Source # | |||||
| Eq a => Eq (TsPoint a) Source # | |||||
| Ord a => Ord (TsPoint a) Source # | |||||
| ToSchema (TsPoint Balance) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Balance) -> Declare (Definitions Schema) NamedSchema # | |||||
| ToSchema (TsPoint IRate) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint IRate) -> Declare (Definitions Schema) NamedSchema # | |||||
| ToSchema (TsPoint Rational) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Rational) -> Declare (Definitions Schema) NamedSchema # | |||||
| ToSchema (TsPoint Bool) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Bool) -> Declare (Definitions Schema) NamedSchema # | |||||
| ToSchema (TsPoint Int) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Int) -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep (TsPoint a) Source # | |||||
Defined in Types type Rep (TsPoint a) = D1 ('MetaData "TsPoint" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "TsPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |||||
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
| FromJSON PoolSource Source # | |||||
Defined in Types | |||||
| ToJSON PoolSource Source # | |||||
Defined in Types Methods toJSON :: PoolSource -> Value # toEncoding :: PoolSource -> Encoding # toJSONList :: [PoolSource] -> Value # toEncodingList :: [PoolSource] -> Encoding # omitField :: PoolSource -> Bool # | |||||
| Generic PoolSource Source # | |||||
Defined in Types Associated Types
| |||||
| Read PoolSource Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS PoolSource # readList :: ReadS [PoolSource] # readPrec :: ReadPrec PoolSource # readListPrec :: ReadPrec [PoolSource] # | |||||
| Show PoolSource Source # | |||||
Defined in Types Methods showsPrec :: Int -> PoolSource -> ShowS # show :: PoolSource -> String # showList :: [PoolSource] -> ShowS # | |||||
| Eq PoolSource Source # | |||||
Defined in Types | |||||
| Ord PoolSource Source # | |||||
Defined in Types Methods compare :: PoolSource -> PoolSource -> Ordering # (<) :: PoolSource -> PoolSource -> Bool # (<=) :: PoolSource -> PoolSource -> Bool # (>) :: PoolSource -> PoolSource -> Bool # (>=) :: PoolSource -> PoolSource -> Bool # max :: PoolSource -> PoolSource -> PoolSource # min :: PoolSource -> PoolSource -> PoolSource # | |||||
| type Rep PoolSource Source # | |||||
Defined in Types type Rep PoolSource = D1 ('MetaData "PoolSource" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "CollectedInterest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedPrincipal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectedRecoveries" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CollectedPrepayment" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedPrepaymentPenalty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectedRental" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CollectedFeePaid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedCash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewDefaults" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NewLosses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewDelinquencies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CurBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurBegBalance" 'PrefixI 'False) (U1 :: Type -> Type))))) | |||||
Instances
| FromJSON a => FromJSON (PerPoint a) Source # | |||||
| ToJSON a => ToJSON (PerPoint a) Source # | |||||
| Generic (PerPoint a) Source # | |||||
Defined in Types Associated Types
| |||||
| Read a => Read (PerPoint a) Source # | |||||
| Show a => Show (PerPoint a) Source # | |||||
| Eq a => Eq (PerPoint a) Source # | |||||
| Ord a => Ord (PerPoint a) Source # | |||||
| type Rep (PerPoint a) Source # | |||||
Defined in Types type Rep (PerPoint a) = D1 ('MetaData "PerPoint" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PerPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |||||
Constructors
| CurrentVal [PerPoint a] | |
| WithTrailVal [PerPoint a] |
Instances
| FromJSON a => FromJSON (PerCurve a) Source # | |||||
| ToJSON a => ToJSON (PerCurve a) Source # | |||||
| Generic (PerCurve a) Source # | |||||
Defined in Types Associated Types
| |||||
| Read a => Read (PerCurve a) Source # | |||||
| Show a => Show (PerCurve a) Source # | |||||
| Eq a => Eq (PerCurve a) Source # | |||||
| Ord a => Ord (PerCurve a) Source # | |||||
| type Rep (PerCurve a) Source # | |||||
Defined in Types type Rep (PerCurve a) = D1 ('MetaData "PerCurve" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "CurrentVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PerPoint a])) :+: C1 ('MetaCons "WithTrailVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PerPoint a]))) | |||||
getValFromPerCurve :: PerCurve a -> DateDirection -> CutoffType -> Int -> Maybe a Source #
Instances
| FromJSON Period Source # | |||||
| ToJSON Period Source # | |||||
| Generic Period Source # | |||||
Defined in Types Associated Types
| |||||
| Show Period Source # | |||||
| Eq Period Source # | |||||
| Ord Period Source # | |||||
| ToSchema Period Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Period -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep Period Source # | |||||
Defined in Types type Rep Period = D1 ('MetaData "Period" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Daily" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Weekly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BiWeekly" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Monthly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Quarterly" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SemiAnnually" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Annually" 'PrefixI 'False) (U1 :: Type -> Type)))) | |||||
Instances
| FromJSON Threshold Source # | |||||
| FromJSONKey Threshold Source # | |||||
Defined in Types Methods | |||||
| ToJSON Threshold Source # | |||||
| ToJSONKey Threshold Source # | |||||
Defined in Types | |||||
| Generic Threshold Source # | |||||
Defined in Types Associated Types
| |||||
| Read Threshold Source # | |||||
| Show Threshold Source # | |||||
| Eq Threshold Source # | |||||
| Ord Threshold Source # | |||||
| type Rep Threshold Source # | |||||
Defined in Types type Rep Threshold = D1 ('MetaData "Threshold" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Below" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqBelow" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Above" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqAbove" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
Constructors
| II | include both start and end date |
| IE | include start date ,but not end date |
| EI | exclude start date but include end date |
| EE | exclude either start date and end date |
| NO_IE | no handling on start date and end date |
Instances
| FromJSON RangeType Source # | |||||
| ToJSON RangeType Source # | |||||
| Generic RangeType Source # | |||||
Defined in Types Associated Types
| |||||
| Read RangeType Source # | |||||
| Show RangeType Source # | |||||
| Eq RangeType Source # | |||||
| Ord RangeType Source # | |||||
| type Rep RangeType Source # | |||||
Defined in Types type Rep RangeType = D1 ('MetaData "RangeType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "II" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EI" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NO_IE" 'PrefixI 'False) (U1 :: Type -> Type)))) | |||||
data CutoffType Source #
Instances
| FromJSON CutoffType Source # | |||||
Defined in Types | |||||
| ToJSON CutoffType Source # | |||||
Defined in Types Methods toJSON :: CutoffType -> Value # toEncoding :: CutoffType -> Encoding # toJSONList :: [CutoffType] -> Value # toEncodingList :: [CutoffType] -> Encoding # omitField :: CutoffType -> Bool # | |||||
| Generic CutoffType Source # | |||||
Defined in Types Associated Types
| |||||
| Read CutoffType Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS CutoffType # readList :: ReadS [CutoffType] # readPrec :: ReadPrec CutoffType # readListPrec :: ReadPrec [CutoffType] # | |||||
| Show CutoffType Source # | |||||
Defined in Types Methods showsPrec :: Int -> CutoffType -> ShowS # show :: CutoffType -> String # showList :: [CutoffType] -> ShowS # | |||||
| Eq CutoffType Source # | |||||
Defined in Types | |||||
| Ord CutoffType Source # | |||||
Defined in Types Methods compare :: CutoffType -> CutoffType -> Ordering # (<) :: CutoffType -> CutoffType -> Bool # (<=) :: CutoffType -> CutoffType -> Bool # (>) :: CutoffType -> CutoffType -> Bool # (>=) :: CutoffType -> CutoffType -> Bool # max :: CutoffType -> CutoffType -> CutoffType # min :: CutoffType -> CutoffType -> CutoffType # | |||||
| ToSchema CutoffType Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy CutoffType -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep CutoffType Source # | |||||
data DealStatus Source #
pricing methods for assets
Constructors
| DealAccelerated (Maybe Date) | Deal is accelerated status with optinal accerlerated date |
| DealDefaulted (Maybe Date) | Deal is defaulted status with optinal default date |
| Amortizing | Deal is amortizing |
| Revolving | Deal is revolving |
| PreClosing DealStatus | Deal is not closed, but has a closing date |
| Warehousing (Maybe DealStatus) | Deal is not closed, but closing date is not determined yet |
| Called | Deal is called |
| Ended Date | Deal is marked as closed |
Instances
| FromJSON DealStatus Source # | |||||
Defined in Types | |||||
| ToJSON DealStatus Source # | |||||
Defined in Types Methods toJSON :: DealStatus -> Value # toEncoding :: DealStatus -> Encoding # toJSONList :: [DealStatus] -> Value # toEncodingList :: [DealStatus] -> Encoding # omitField :: DealStatus -> Bool # | |||||
| Generic DealStatus Source # | |||||
Defined in Types Associated Types
| |||||
| Read DealStatus Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS DealStatus # readList :: ReadS [DealStatus] # readPrec :: ReadPrec DealStatus # readListPrec :: ReadPrec [DealStatus] # | |||||
| Show DealStatus Source # | |||||
Defined in Types Methods showsPrec :: Int -> DealStatus -> ShowS # show :: DealStatus -> String # showList :: [DealStatus] -> ShowS # | |||||
| Eq DealStatus Source # | |||||
Defined in Types | |||||
| Ord DealStatus Source # | |||||
Defined in Types Methods compare :: DealStatus -> DealStatus -> Ordering # (<) :: DealStatus -> DealStatus -> Bool # (<=) :: DealStatus -> DealStatus -> Bool # (>) :: DealStatus -> DealStatus -> Bool # (>=) :: DealStatus -> DealStatus -> Bool # max :: DealStatus -> DealStatus -> DealStatus # min :: DealStatus -> DealStatus -> DealStatus # | |||||
| type Rep DealStatus Source # | |||||
Defined in Types type Rep DealStatus = D1 ('MetaData "DealStatus" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "DealAccelerated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date))) :+: C1 ('MetaCons "DealDefaulted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)))) :+: (C1 ('MetaCons "Amortizing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Revolving" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PreClosing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :+: C1 ('MetaCons "Warehousing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DealStatus)))) :+: (C1 ('MetaCons "Called" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ended" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))))) | |||||
Constructors
| LPR5Y | |
| LPR1Y | |
| LIBOR1M | |
| LIBOR3M | |
| LIBOR6M | |
| LIBOR1Y | |
| USTSY1Y | |
| USTSY2Y | |
| USTSY3Y | |
| USTSY5Y | |
| USTSY7Y | |
| USTSY10Y | |
| USTSY20Y | |
| USTSY30Y | |
| USCMT1Y | |
| PRIME | |
| COFI | |
| SOFR1M | |
| SOFR3M | |
| SOFR6M | |
| SOFR1Y | |
| EURIBOR1M | |
| EURIBOR3M | |
| EURIBOR6M | |
| EURIBOR12M | |
| BBSW | |
| IRPH | |
| SONIA |
Instances
| FromJSON Index Source # | |||||
| ToJSON Index Source # | |||||
| Generic Index Source # | |||||
Defined in Types Associated Types
| |||||
| Read Index Source # | |||||
| Show Index Source # | |||||
| Eq Index Source # | |||||
| Ord Index Source # | |||||
| ToSchema Index Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Index -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep Index Source # | |||||
Defined in Types type Rep Index = D1 ('MetaData "Index" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "LPR5Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LPR1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LIBOR1M" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LIBOR3M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LIBOR6M" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LIBOR1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY1Y" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "USTSY2Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "USTSY3Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY5Y" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "USTSY7Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY10Y" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "USTSY20Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY30Y" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "USCMT1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PRIME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COFI" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SOFR1M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SOFR3M" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SOFR6M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SOFR1Y" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EURIBOR1M" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EURIBOR3M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EURIBOR6M" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EURIBOR12M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BBSW" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IRPH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SONIA" 'PrefixI 'False) (U1 :: Type -> Type)))))) | |||||
Instances
| FromJSON Cmp Source # | |||||
| ToJSON Cmp Source # | |||||
| Generic Cmp Source # | |||||
Defined in Types Associated Types
| |||||
| Read Cmp Source # | |||||
| Show Cmp Source # | |||||
| Eq Cmp Source # | |||||
| Ord Cmp Source # | |||||
| type Rep Cmp Source # | |||||
Defined in Types type Rep Cmp = D1 ('MetaData "Cmp" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "G" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "E" 'PrefixI 'False) (U1 :: Type -> Type)))) | |||||
class TimeSeries ts where Source #
different types of curves, which determine how to interpolate between two points
Minimal complete definition
Methods
cmp :: ts -> ts -> Ordering Source #
sameDate :: ts -> ts -> Bool Source #
getDate :: ts -> Date Source #
getDates :: [ts] -> [Date] Source #
filterByDate :: [ts] -> Date -> [ts] Source #
sliceBy :: RangeType -> StartDate -> EndDate -> [ts] -> [ts] Source #
cutBy :: CutoffType -> DateDirection -> Date -> [ts] -> [ts] Source #
cmpWith :: ts -> Date -> Ordering Source #
isAfter :: ts -> Date -> Bool Source #
isOnAfter :: ts -> Date -> Bool Source #
isBefore :: ts -> Date -> Bool Source #
isOnBefore :: ts -> Date -> Bool Source #
splitBy :: Date -> CutoffType -> [ts] -> ([ts], [ts]) Source #
Instances
| TimeSeries AccrualPeriod Source # | |
Defined in AssetClass.AssetBase Methods cmp :: AccrualPeriod -> AccrualPeriod -> Ordering Source # sameDate :: AccrualPeriod -> AccrualPeriod -> Bool Source # getDate :: AccrualPeriod -> Date Source # getDates :: [AccrualPeriod] -> [Date] Source # filterByDate :: [AccrualPeriod] -> Date -> [AccrualPeriod] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [AccrualPeriod] -> [AccrualPeriod] Source # cutBy :: CutoffType -> DateDirection -> Date -> [AccrualPeriod] -> [AccrualPeriod] Source # cmpWith :: AccrualPeriod -> Date -> Ordering Source # isAfter :: AccrualPeriod -> Date -> Bool Source # isOnAfter :: AccrualPeriod -> Date -> Bool Source # isBefore :: AccrualPeriod -> Date -> Bool Source # isOnBefore :: AccrualPeriod -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [AccrualPeriod] -> ([AccrualPeriod], [AccrualPeriod]) Source # getByDate :: Date -> [AccrualPeriod] -> Maybe AccrualPeriod Source # | |
| 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 # | |
| TimeSeries ActionOnDate Source # | |
Defined in Deal.DealBase Methods cmp :: ActionOnDate -> ActionOnDate -> Ordering Source # sameDate :: ActionOnDate -> ActionOnDate -> Bool Source # getDate :: ActionOnDate -> Date Source # getDates :: [ActionOnDate] -> [Date] Source # filterByDate :: [ActionOnDate] -> Date -> [ActionOnDate] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [ActionOnDate] -> [ActionOnDate] Source # cutBy :: CutoffType -> DateDirection -> Date -> [ActionOnDate] -> [ActionOnDate] Source # cmpWith :: ActionOnDate -> Date -> Ordering Source # isAfter :: ActionOnDate -> Date -> Bool Source # isOnAfter :: ActionOnDate -> Date -> Bool Source # isBefore :: ActionOnDate -> Date -> Bool Source # isOnBefore :: ActionOnDate -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [ActionOnDate] -> ([ActionOnDate], [ActionOnDate]) Source # getByDate :: Date -> [ActionOnDate] -> Maybe ActionOnDate Source # | |
| TimeSeries Txn Source # | |
Defined in Stmt Methods cmp :: Txn -> Txn -> Ordering Source # sameDate :: Txn -> Txn -> Bool Source # getDate :: Txn -> Date Source # getDates :: [Txn] -> [Date] Source # filterByDate :: [Txn] -> Date -> [Txn] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [Txn] -> [Txn] Source # cutBy :: CutoffType -> DateDirection -> Date -> [Txn] -> [Txn] Source # cmpWith :: Txn -> Date -> Ordering Source # isAfter :: Txn -> Date -> Bool Source # isOnAfter :: Txn -> Date -> Bool Source # isBefore :: Txn -> Date -> Bool Source # isOnBefore :: Txn -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [Txn] -> ([Txn], [Txn]) Source # | |
| TimeSeries (TsPoint a) Source # | |
Defined in Types Methods cmp :: TsPoint a -> TsPoint a -> Ordering Source # sameDate :: TsPoint a -> TsPoint a -> Bool Source # getDate :: TsPoint a -> Date Source # getDates :: [TsPoint a] -> [Date] Source # filterByDate :: [TsPoint a] -> Date -> [TsPoint a] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [TsPoint a] -> [TsPoint a] Source # cutBy :: CutoffType -> DateDirection -> Date -> [TsPoint a] -> [TsPoint a] Source # cmpWith :: TsPoint a -> Date -> Ordering Source # isAfter :: TsPoint a -> Date -> Bool Source # isOnAfter :: TsPoint a -> Date -> Bool Source # isBefore :: TsPoint a -> Date -> Bool Source # isOnBefore :: TsPoint a -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [TsPoint a] -> ([TsPoint a], [TsPoint a]) Source # getByDate :: Date -> [TsPoint a] -> Maybe (TsPoint a) Source # | |
type PrepaymentPenalty = Balance Source #
deal level cumulative statistics
Constructors
| EqToLeft | |
| EqToRight | |
| EqToLeftKeepOne | |
| EqToLeftKeepOnes |
Instances
| Generic SplitType Source # | |||||
Defined in Types Associated Types
| |||||
| Show SplitType Source # | |||||
| Eq SplitType Source # | |||||
| type Rep SplitType Source # | |||||
Defined in Types type Rep SplitType = D1 ('MetaData "SplitType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "EqToLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqToRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EqToLeftKeepOne" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqToLeftKeepOnes" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
Instances
| FromJSON BookItem Source # | |||||
| ToJSON BookItem Source # | |||||
| Generic BookItem Source # | |||||
Defined in Types Associated Types
| |||||
| Read BookItem Source # | |||||
| Show BookItem Source # | |||||
| Eq BookItem Source # | |||||
| type Rep BookItem Source # | |||||
Defined in Types type Rep BookItem = D1 ('MetaData "BookItem" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Item" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "ParentItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItems))) | |||||
data BalanceSheetReport Source #
Constructors
| BalanceSheetReport | snapshot date of the balance sheet |
Instances
| FromJSON BalanceSheetReport Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser BalanceSheetReport # parseJSONList :: Value -> Parser [BalanceSheetReport] # | |||||
| ToJSON BalanceSheetReport Source # | |||||
Defined in Types Methods toJSON :: BalanceSheetReport -> Value # toEncoding :: BalanceSheetReport -> Encoding # toJSONList :: [BalanceSheetReport] -> Value # toEncodingList :: [BalanceSheetReport] -> Encoding # omitField :: BalanceSheetReport -> Bool # | |||||
| Generic BalanceSheetReport Source # | |||||
Defined in Types Associated Types
Methods from :: BalanceSheetReport -> Rep BalanceSheetReport x # to :: Rep BalanceSheetReport x -> BalanceSheetReport # | |||||
| Read BalanceSheetReport Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS BalanceSheetReport # readList :: ReadS [BalanceSheetReport] # | |||||
| Show BalanceSheetReport Source # | |||||
Defined in Types Methods showsPrec :: Int -> BalanceSheetReport -> ShowS # show :: BalanceSheetReport -> String # showList :: [BalanceSheetReport] -> ShowS # | |||||
| Eq BalanceSheetReport Source # | |||||
Defined in Types Methods (==) :: BalanceSheetReport -> BalanceSheetReport -> Bool # (/=) :: BalanceSheetReport -> BalanceSheetReport -> Bool # | |||||
| type Rep BalanceSheetReport Source # | |||||
Defined in Types type Rep BalanceSheetReport = D1 ('MetaData "BalanceSheetReport" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BalanceSheetReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "asset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "liability") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem)) :*: (S1 ('MetaSel ('Just "equity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "reportDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) | |||||
data CashflowReport Source #
Constructors
| CashflowReport | |
Instances
| FromJSON CashflowReport Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser CashflowReport # parseJSONList :: Value -> Parser [CashflowReport] # | |||||
| ToJSON CashflowReport Source # | |||||
Defined in Types Methods toJSON :: CashflowReport -> Value # toEncoding :: CashflowReport -> Encoding # toJSONList :: [CashflowReport] -> Value # toEncodingList :: [CashflowReport] -> Encoding # omitField :: CashflowReport -> Bool # | |||||
| Generic CashflowReport Source # | |||||
Defined in Types Associated Types
Methods from :: CashflowReport -> Rep CashflowReport x # to :: Rep CashflowReport x -> CashflowReport # | |||||
| Read CashflowReport Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS CashflowReport # readList :: ReadS [CashflowReport] # | |||||
| Show CashflowReport Source # | |||||
Defined in Types Methods showsPrec :: Int -> CashflowReport -> ShowS # show :: CashflowReport -> String # showList :: [CashflowReport] -> ShowS # | |||||
| Eq CashflowReport Source # | |||||
Defined in Types Methods (==) :: CashflowReport -> CashflowReport -> Bool # (/=) :: CashflowReport -> CashflowReport -> Bool # | |||||
| type Rep CashflowReport Source # | |||||
Defined in Types type Rep CashflowReport = D1 ('MetaData "CashflowReport" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "CashflowReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "inflow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "outflow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem)) :*: (S1 ('MetaSel ('Just "net") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: (S1 ('MetaSel ('Just "startDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Just "endDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))))) | |||||
data RateAssumption Source #
Constructors
| RateCurve Index Ts | a rate curve ,which value of rates depends on time |
| RateFlat Index IRate | a rate constant |
Instances
| FromJSON RateAssumption Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser RateAssumption # parseJSONList :: Value -> Parser [RateAssumption] # | |||||
| ToJSON RateAssumption Source # | |||||
Defined in Types Methods toJSON :: RateAssumption -> Value # toEncoding :: RateAssumption -> Encoding # toJSONList :: [RateAssumption] -> Value # toEncodingList :: [RateAssumption] -> Encoding # omitField :: RateAssumption -> Bool # | |||||
| Generic RateAssumption Source # | |||||
Defined in Types Associated Types
Methods from :: RateAssumption -> Rep RateAssumption x # to :: Rep RateAssumption x -> RateAssumption # | |||||
| Show RateAssumption Source # | |||||
Defined in Types Methods showsPrec :: Int -> RateAssumption -> ShowS # show :: RateAssumption -> String # showList :: [RateAssumption] -> ShowS # | |||||
| type Rep RateAssumption Source # | |||||
Defined in Types type Rep RateAssumption = D1 ('MetaData "RateAssumption" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "RateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: C1 ('MetaCons "RateFlat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Index) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate))) | |||||
type PrepaymentRate = Rate Source #
type DefaultRate = Rate Source #
type RecoveryRate = Rate Source #
type RemainTerms = Int Source #
type Prepayment = Balance Source #
Constructors
| ThresholdTable [(a, b)] |
Instances
| (FromJSON a, FromJSON b) => FromJSON (Table a b) Source # | |
| (ToJSON a, ToJSON b) => ToJSON (Table a b) Source # | |
| Generic (Table a b) Source # | |
| (Read a, Read b) => Read (Table a b) Source # | |
| (Show a, Show b) => Show (Table a b) Source # | |
| (Eq a, Eq b) => Eq (Table a b) Source # | |
| (Ord a, Ord b) => Ord (Table a b) Source # | |
| type Rep (Table a b) Source # | |
direction of the transaction, in terms of the book keeping
Instances
| FromJSON Direction Source # | |
| ToJSON Direction Source # | |
| Generic Direction Source # | |
| Read Direction Source # | |
| Show Direction Source # | |
| Eq Direction Source # | |
| Ord Direction Source # | |
| ToSchema Direction Source # | |
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Direction -> Declare (Definitions Schema) NamedSchema # | |
| type Rep Direction Source # | |
type BorrowerNum = Int Source #
Constructors
| BondTxn Date Balance Interest Principal IRate Cash DueInt DueIoI (Maybe Float) TxnComment | bond transaction record for interest and principal |
| AccTxn Date Balance Amount TxnComment | account transaction record |
| ExpTxn Date Balance Amount Balance TxnComment | expense transaction record |
| SupportTxn Date (Maybe Balance) Balance DueInt DuePremium Cash TxnComment | liquidity provider transaction record |
| IrsTxn Date Balance Amount IRate IRate Balance TxnComment | interest swap transaction record |
| EntryTxn Date Balance Amount TxnComment | ledger book entry |
| TrgTxn Date Bool TxnComment |
Instances
| TimeSeries Txn Source # | |||||
Defined in Stmt Methods cmp :: Txn -> Txn -> Ordering Source # sameDate :: Txn -> Txn -> Bool Source # getDate :: Txn -> Date Source # getDates :: [Txn] -> [Date] Source # filterByDate :: [Txn] -> Date -> [Txn] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [Txn] -> [Txn] Source # cutBy :: CutoffType -> DateDirection -> Date -> [Txn] -> [Txn] Source # cmpWith :: Txn -> Date -> Ordering Source # isAfter :: Txn -> Date -> Bool Source # isOnAfter :: Txn -> Date -> Bool Source # isBefore :: Txn -> Date -> Bool Source # isOnBefore :: Txn -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [Txn] -> ([Txn], [Txn]) Source # | |||||
| FromJSON Txn Source # | |||||
| ToJSON Txn Source # | |||||
| Generic Txn Source # | |||||
Defined in Types Associated Types
| |||||
| Read Txn Source # | |||||
| Show Txn Source # | |||||
| Eq Txn Source # | |||||
| Ord Txn Source # | |||||
| type Rep Txn Source # | |||||
Defined in Types type Rep Txn = D1 ('MetaData "Txn" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "BondTxn" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interest) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Principal) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueIoI) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Float)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "AccTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "ExpTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))))) :+: ((C1 ('MetaCons "SupportTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Balance)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DuePremium)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))) :+: C1 ('MetaCons "IrsTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "EntryTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "TrgTxn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))))) | |||||
data TxnComment Source #
transaction record in each entity
Constructors
| PayInt [BondName] | |
| PayYield BondName | |
| PayPrin [BondName] | |
| PayGroupPrin [BondName] | |
| PayGroupInt [BondName] | |
| WriteOff BondName Balance | |
| FundWith BondName Balance | |
| PayPrinResidual [BondName] | |
| PayFee FeeName | |
| SeqPayFee [FeeName] | |
| PayFeeYield FeeName | |
| Transfer AccName AccName | |
| TransferBy AccName AccName Limit | |
| BookLedgerBy BookDirection String | |
| PoolInflow (Maybe [PoolId]) PoolSource | |
| LiquidationProceeds [PoolId] | |
| LiquidationSupport String | |
| LiquidationDraw | |
| LiquidationRepay String | |
| LiquidationSupportInt Balance Balance | |
| BankInt | |
| SupportDraw | |
| Empty | |
| Tag String | |
| UsingDS DealStats | |
| SwapAccrue | |
| SwapInSettle String | |
| SwapOutSettle String | |
| PurchaseAsset String Balance | |
| IssuanceProceeds String | |
| TxnDirection BookDirection | |
| TxnComments [TxnComment] |
Instances
| FromJSON TxnComment Source # | |||||
Defined in Types | |||||
| ToJSON TxnComment Source # | |||||
Defined in Types Methods toJSON :: TxnComment -> Value # toEncoding :: TxnComment -> Encoding # toJSONList :: [TxnComment] -> Value # toEncodingList :: [TxnComment] -> Encoding # omitField :: TxnComment -> Bool # | |||||
| Generic TxnComment Source # | |||||
Defined in Types Associated Types
| |||||
| Read TxnComment Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS TxnComment # readList :: ReadS [TxnComment] # readPrec :: ReadPrec TxnComment # readListPrec :: ReadPrec [TxnComment] # | |||||
| Show TxnComment Source # | |||||
Defined in Types Methods showsPrec :: Int -> TxnComment -> ShowS # show :: TxnComment -> String # showList :: [TxnComment] -> ShowS # | |||||
| Eq TxnComment Source # | |||||
Defined in Types | |||||
| Ord TxnComment Source # | |||||
Defined in Types Methods compare :: TxnComment -> TxnComment -> Ordering # (<) :: TxnComment -> TxnComment -> Bool # (<=) :: TxnComment -> TxnComment -> Bool # (>) :: TxnComment -> TxnComment -> Bool # (>=) :: TxnComment -> TxnComment -> Bool # max :: TxnComment -> TxnComment -> TxnComment # min :: TxnComment -> TxnComment -> TxnComment # | |||||
| type Rep TxnComment Source # | |||||
Defined in Types type Rep TxnComment = D1 ('MetaData "TxnComment" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((((C1 ('MetaCons "PayInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "PayYield" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "PayPrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "PayGroupPrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "PayGroupInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "WriteOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: (C1 ('MetaCons "FundWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "PayPrinResidual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))))) :+: (((C1 ('MetaCons "PayFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)) :+: C1 ('MetaCons "SeqPayFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]))) :+: (C1 ('MetaCons "PayFeeYield" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)) :+: C1 ('MetaCons "Transfer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName)))) :+: ((C1 ('MetaCons "TransferBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Limit))) :+: C1 ('MetaCons "BookLedgerBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "PoolInflow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource)) :+: C1 ('MetaCons "LiquidationProceeds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolId])))))) :+: ((((C1 ('MetaCons "LiquidationSupport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "LiquidationDraw" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LiquidationRepay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "LiquidationSupportInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: ((C1 ('MetaCons "BankInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SupportDraw" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) :+: (((C1 ('MetaCons "UsingDS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "SwapAccrue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SwapInSettle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "SwapOutSettle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "PurchaseAsset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "IssuanceProceeds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "TxnDirection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection)) :+: C1 ('MetaCons "TxnComments" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxnComment]))))))) | |||||
data RoundingBy a Source #
Constructors
| RoundCeil a | |
| RoundFloor a |
Instances
| FromJSON a => FromJSON (RoundingBy a) Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser (RoundingBy a) # parseJSONList :: Value -> Parser [RoundingBy a] # omittedField :: Maybe (RoundingBy a) # | |||||
| ToJSON a => ToJSON (RoundingBy a) Source # | |||||
Defined in Types Methods toJSON :: RoundingBy a -> Value # toEncoding :: RoundingBy a -> Encoding # toJSONList :: [RoundingBy a] -> Value # toEncodingList :: [RoundingBy a] -> Encoding # omitField :: RoundingBy a -> Bool # | |||||
| Generic (RoundingBy a) Source # | |||||
Defined in Types Associated Types
| |||||
| Read a => Read (RoundingBy a) Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS (RoundingBy a) # readList :: ReadS [RoundingBy a] # readPrec :: ReadPrec (RoundingBy a) # readListPrec :: ReadPrec [RoundingBy a] # | |||||
| Show a => Show (RoundingBy a) Source # | |||||
Defined in Types Methods showsPrec :: Int -> RoundingBy a -> ShowS # show :: RoundingBy a -> String # showList :: [RoundingBy a] -> ShowS # | |||||
| Eq a => Eq (RoundingBy a) Source # | |||||
Defined in Types | |||||
| Ord a => Ord (RoundingBy a) Source # | |||||
Defined in Types Methods compare :: RoundingBy a -> RoundingBy a -> Ordering # (<) :: RoundingBy a -> RoundingBy a -> Bool # (<=) :: RoundingBy a -> RoundingBy a -> Bool # (>) :: RoundingBy a -> RoundingBy a -> Bool # (>=) :: RoundingBy a -> RoundingBy a -> Bool # max :: RoundingBy a -> RoundingBy a -> RoundingBy a # min :: RoundingBy a -> RoundingBy a -> RoundingBy a # | |||||
| ToSchema (RoundingBy IRate) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (RoundingBy IRate) -> Declare (Definitions Schema) NamedSchema # | |||||
| type Rep (RoundingBy a) Source # | |||||
Defined in Types type Rep (RoundingBy a) = D1 ('MetaData "RoundingBy" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "RoundCeil" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "RoundFloor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |||||
data DateDirection Source #
Instances
| Generic DateDirection Source # | |||||
Defined in Types Associated Types
| |||||
| Read DateDirection Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS DateDirection # readList :: ReadS [DateDirection] # | |||||
| Show DateDirection Source # | |||||
Defined in Types Methods showsPrec :: Int -> DateDirection -> ShowS # show :: DateDirection -> String # showList :: [DateDirection] -> ShowS # | |||||
| type Rep DateDirection Source # | |||||
data BookDirection Source #
Instances
| FromJSON BookDirection Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser BookDirection # parseJSONList :: Value -> Parser [BookDirection] # | |||||
| ToJSON BookDirection Source # | |||||
Defined in Types Methods toJSON :: BookDirection -> Value # toEncoding :: BookDirection -> Encoding # toJSONList :: [BookDirection] -> Value # toEncodingList :: [BookDirection] -> Encoding # omitField :: BookDirection -> Bool # | |||||
| Generic BookDirection Source # | |||||
Defined in Types Associated Types
| |||||
| Read BookDirection Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS BookDirection # readList :: ReadS [BookDirection] # | |||||
| Show BookDirection Source # | |||||
Defined in Types Methods showsPrec :: Int -> BookDirection -> ShowS # show :: BookDirection -> String # showList :: [BookDirection] -> ShowS # | |||||
| Eq BookDirection Source # | |||||
Defined in Types Methods (==) :: BookDirection -> BookDirection -> Bool # (/=) :: BookDirection -> BookDirection -> Bool # | |||||
| Ord BookDirection Source # | |||||
Defined in Types Methods compare :: BookDirection -> BookDirection -> Ordering # (<) :: BookDirection -> BookDirection -> Bool # (<=) :: BookDirection -> BookDirection -> Bool # (>) :: BookDirection -> BookDirection -> Bool # (>=) :: BookDirection -> BookDirection -> Bool # max :: BookDirection -> BookDirection -> BookDirection # min :: BookDirection -> BookDirection -> BookDirection # | |||||
| type Rep BookDirection Source # | |||||
different status of the deal
Constructors
| EndCollection | | collection period HERE collection action , waterfall action |
| EndCollectionWF | | collection period collection action HERE, waterfall action |
| BeginDistributionWF | | collection period collection action , HEREwaterfall action |
| EndDistributionWF | | collection period collection action , waterfall actionHERE |
| InWF | | collection period collection action , waterfall HERE action |
Instances
| FromJSON DealCycle Source # | |||||
| FromJSONKey DealCycle Source # | |||||
Defined in Types Methods | |||||
| ToJSON DealCycle Source # | |||||
| ToJSONKey DealCycle Source # | |||||
Defined in Types | |||||
| Generic DealCycle Source # | |||||
Defined in Types Associated Types
| |||||
| Read DealCycle Source # | |||||
| Show DealCycle Source # | |||||
| Eq DealCycle Source # | |||||
| Ord DealCycle Source # | |||||
| type Rep DealCycle Source # | |||||
Defined in Types type Rep DealCycle = D1 ('MetaData "DealCycle" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "EndCollection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndCollectionWF" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeginDistributionWF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndDistributionWF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InWF" 'PrefixI 'False) (U1 :: Type -> Type)))) | |||||
Constructors
| DuePct Rate | up to % of total amount due |
| DueCapAmt Balance | up to $ amount |
| KeepBalAmt DealStats | pay till a certain amount remains in an account |
| DS DealStats | transfer with limit described by a |
| RemainBalPct Rate | pay till remain balance equals to a percentage of |
| TillTarget | transfer amount which make target account up reach reserve balanace |
| TillSource | transfer amount out till source account down back to reserve balance |
| Multiple Limit Float | factor of a limit |
Instances
| FromJSON Limit Source # | |||||
| ToJSON Limit Source # | |||||
| Generic Limit Source # | |||||
Defined in Types Associated Types
| |||||
| Read Limit Source # | |||||
| Show Limit Source # | |||||
| Eq Limit Source # | |||||
| Ord Limit Source # | |||||
| type Rep Limit Source # | |||||
Defined in Types type Rep Limit = D1 ('MetaData "Limit" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "DuePct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "DueCapAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: (C1 ('MetaCons "KeepBalAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "DS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))) :+: ((C1 ('MetaCons "RemainBalPct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "TillTarget" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TillSource" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Multiple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Limit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))) | |||||
Constructors
| IfZero DealStats | |
| If Cmp DealStats Balance | |
| IfRate Cmp DealStats Micro | |
| IfCurve Cmp DealStats Ts | |
| IfByPeriodCurve Cmp DealStats DealStats (PerCurve Balance) | |
| IfRateCurve Cmp DealStats Ts | |
| IfRateByPeriodCurve Cmp DealStats DealStats (PerCurve Rate) | |
| IfIntCurve Cmp DealStats Ts | |
| IfInt Cmp DealStats Int | |
| IfIntBetween DealStats RangeType Int Int | |
| IfIntIn DealStats [Int] | |
| IfDate Cmp Date | |
| IfDateBetween RangeType Date Date | |
| IfDateIn Dates | |
| IfBool DealStats Bool | |
| If2 Cmp DealStats DealStats | |
| IfRate2 Cmp DealStats DealStats | |
| IfInt2 Cmp DealStats DealStats | |
| IfDealStatus DealStatus | IfRateCurve DealStats Cmp Ts |
| Always Bool | |
| IfNot Pre | |
| Any [Pre] | |
| All [Pre] |
Instances
| FromJSON Pre Source # | |||||
| ToJSON Pre Source # | |||||
| Generic Pre Source # | |||||
Defined in Types Associated Types
| |||||
| Read Pre Source # | |||||
| Show Pre Source # | |||||
| Eq Pre Source # | |||||
| Ord Pre Source # | |||||
| type Rep Pre Source # | |||||
Defined in Types type Rep Pre = D1 ('MetaData "Pre" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "IfZero" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "If" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: (C1 ('MetaCons "IfRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro))) :+: (C1 ('MetaCons "IfCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) :+: C1 ('MetaCons "IfByPeriodCurve" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCurve Balance))))))) :+: ((C1 ('MetaCons "IfRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) :+: (C1 ('MetaCons "IfRateByPeriodCurve" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCurve Rate)))) :+: C1 ('MetaCons "IfIntCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))))) :+: (C1 ('MetaCons "IfInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "IfIntBetween" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: C1 ('MetaCons "IfIntIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))))) :+: (((C1 ('MetaCons "IfDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "IfDateBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))) :+: C1 ('MetaCons "IfDateIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dates)))) :+: (C1 ('MetaCons "IfBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "If2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "IfRate2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))))) :+: ((C1 ('MetaCons "IfInt2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: (C1 ('MetaCons "IfDealStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :+: C1 ('MetaCons "Always" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: (C1 ('MetaCons "IfNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pre)) :+: (C1 ('MetaCons "Any" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])) :+: C1 ('MetaCons "All" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre]))))))) | |||||
class Liable lb where Source #
Methods
isPaidOff :: lb -> Bool Source #
getCurBalance :: lb -> Balance Source #
getCurRate :: lb -> IRate Source #
getOriginBalance :: lb -> Balance Source #
getOriginDate :: lb -> Date Source #
getAccrueBegDate :: lb -> Date Source #
getDueInt :: lb -> Balance Source #
getDueIntAt :: lb -> Int -> Balance Source #
getDueIntOverInt :: lb -> Balance Source #
getDueIntOverIntAt :: lb -> Int -> Balance Source #
getTotalDueInt :: lb -> Balance Source #
getTotalDueIntAt :: lb -> Int -> Balance Source #
getOutstandingAmount :: lb -> Balance Source #
Instances
| Liable LiqFacility Source # | |
Defined in CreditEnhancement Methods isPaidOff :: LiqFacility -> Bool Source # getCurBalance :: LiqFacility -> Balance Source # getCurRate :: LiqFacility -> IRate Source # getOriginBalance :: LiqFacility -> Balance Source # getOriginDate :: LiqFacility -> Date Source # getAccrueBegDate :: LiqFacility -> Date Source # getDueInt :: LiqFacility -> Balance Source # getDueIntAt :: LiqFacility -> Int -> Balance Source # getDueIntOverInt :: LiqFacility -> Balance Source # getDueIntOverIntAt :: LiqFacility -> Int -> Balance Source # getTotalDueInt :: LiqFacility -> Balance Source # getTotalDueIntAt :: LiqFacility -> Int -> Balance Source # | |
| Liable Fee Source # | |
Defined in Expense Methods isPaidOff :: Fee -> Bool Source # getCurBalance :: Fee -> Balance Source # getCurRate :: Fee -> IRate Source # getOriginBalance :: Fee -> Balance Source # getOriginDate :: Fee -> Date Source # getAccrueBegDate :: Fee -> Date Source # getDueInt :: Fee -> Balance Source # getDueIntAt :: Fee -> Int -> Balance Source # getDueIntOverInt :: Fee -> Balance Source # getDueIntOverIntAt :: Fee -> Int -> Balance Source # getTotalDueInt :: Fee -> Balance Source # getTotalDueIntAt :: Fee -> Int -> Balance Source # getOutstandingAmount :: Fee -> Balance Source # | |
| Liable RateSwap Source # | |
Defined in Hedge Methods isPaidOff :: RateSwap -> Bool Source # getCurBalance :: RateSwap -> Balance Source # getCurRate :: RateSwap -> IRate Source # getOriginBalance :: RateSwap -> Balance Source # getOriginDate :: RateSwap -> Date Source # getAccrueBegDate :: RateSwap -> Date Source # getDueInt :: RateSwap -> Balance Source # getDueIntAt :: RateSwap -> Int -> Balance Source # getDueIntOverInt :: RateSwap -> Balance Source # getDueIntOverIntAt :: RateSwap -> Int -> Balance Source # getTotalDueInt :: RateSwap -> Balance Source # | |
| Liable SRT Source # | |
Defined in Hedge Methods isPaidOff :: SRT -> Bool Source # getCurBalance :: SRT -> Balance Source # getCurRate :: SRT -> IRate Source # getOriginBalance :: SRT -> Balance Source # getOriginDate :: SRT -> Date Source # getAccrueBegDate :: SRT -> Date Source # getDueInt :: SRT -> Balance Source # getDueIntAt :: SRT -> Int -> Balance Source # getDueIntOverInt :: SRT -> Balance Source # getDueIntOverIntAt :: SRT -> Int -> Balance Source # getTotalDueInt :: SRT -> Balance Source # getTotalDueIntAt :: SRT -> Int -> Balance Source # getOutstandingAmount :: SRT -> Balance Source # | |
| Liable Bond Source # | |
Defined in Liability Methods isPaidOff :: Bond -> Bool Source # getCurBalance :: Bond -> Balance Source # getCurRate :: Bond -> IRate Source # getOriginBalance :: Bond -> Balance Source # getOriginDate :: Bond -> Date Source # getAccrueBegDate :: Bond -> Date Source # getDueInt :: Bond -> Balance Source # getDueIntAt :: Bond -> Int -> Balance Source # getDueIntOverInt :: Bond -> Balance Source # getDueIntOverIntAt :: Bond -> Int -> Balance Source # getTotalDueInt :: Bond -> Balance Source # getTotalDueIntAt :: Bond -> Int -> Balance Source # getOutstandingAmount :: Bond -> Balance Source # | |
type CumDefault = Balance Source #
type CumPrincipal = Balance Source #
type CumRecovery = Balance Source #
Constructors
| PoolName String | pool name |
| PoolConsol | consolidate pool ( the only pool ) |
| DealBondFlow DealName String Date Rate | bond flow from deal |
Instances
| FromJSON PoolId Source # | |||||
| FromJSONKey PoolId Source # | different types of waterfall execution | ||||
Defined in Types | |||||
| ToJSON PoolId Source # | |||||
| ToJSONKey PoolId Source # | |||||
Defined in Types | |||||
| Generic PoolId Source # | |||||
Defined in Types Associated Types
| |||||
| Read PoolId Source # | |||||
| Show PoolId Source # | |||||
| Eq PoolId Source # | |||||
| Ord PoolId Source # | |||||
| type Rep PoolId Source # | |||||
Defined in Types type Rep PoolId = D1 ('MetaData "PoolId" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PoolName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "PoolConsol" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DealBondFlow" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))))) | |||||
lookupIntervalTable :: Ord a => Table a b -> Direction -> (a -> Bool) -> Maybe ((a, b), (a, b)) Source #
data CutoffFields Source #
Constructors
| IssuanceBalance | pool issuance balance |
| HistoryRecoveries | cumulative recoveries |
| HistoryInterest | cumulative interest collected |
| HistoryPrepayment | cumulative prepayment collected |
| HistoryPrepaymentPentalty | cumulative prepayment collected |
| HistoryPrincipal | cumulative principal collected |
| HistoryRental | cumulative rental collected |
| HistoryDefaults | cumulative default balance |
| HistoryDelinquency | cumulative delinquency balance |
| HistoryLoss | cumulative loss/write-off balance |
| HistoryCash | cumulative cash |
| HistoryFeePaid | |
| AccruedInterest | accrued interest at closing |
| RuntimeCurrentPoolBalance | current pool balance |
Instances
| FromJSON CutoffFields Source # | |||||
Defined in Types | |||||
| FromJSONKey CutoffFields Source # | |||||
Defined in Types | |||||
| ToJSON CutoffFields Source # | |||||
Defined in Types Methods toJSON :: CutoffFields -> Value # toEncoding :: CutoffFields -> Encoding # toJSONList :: [CutoffFields] -> Value # toEncodingList :: [CutoffFields] -> Encoding # omitField :: CutoffFields -> Bool # | |||||
| ToJSONKey CutoffFields Source # | |||||
Defined in Types Methods | |||||
| Generic CutoffFields Source # | |||||
Defined in Types Associated Types
| |||||
| Read CutoffFields Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS CutoffFields # readList :: ReadS [CutoffFields] # | |||||
| Show CutoffFields Source # | |||||
Defined in Types Methods showsPrec :: Int -> CutoffFields -> ShowS # show :: CutoffFields -> String # showList :: [CutoffFields] -> ShowS # | |||||
| NFData CutoffFields Source # | |||||
Defined in Types Methods rnf :: CutoffFields -> () # | |||||
| Eq CutoffFields Source # | |||||
Defined in Types | |||||
| Ord CutoffFields Source # | |||||
Defined in Types Methods compare :: CutoffFields -> CutoffFields -> Ordering # (<) :: CutoffFields -> CutoffFields -> Bool # (<=) :: CutoffFields -> CutoffFields -> Bool # (>) :: CutoffFields -> CutoffFields -> Bool # (>=) :: CutoffFields -> CutoffFields -> Bool # max :: CutoffFields -> CutoffFields -> CutoffFields # min :: CutoffFields -> CutoffFields -> CutoffFields # | |||||
| type Rep CutoffFields Source # | |||||
Defined in Types type Rep CutoffFields = D1 ('MetaData "CutoffFields" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "IssuanceBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HistoryRecoveries" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryInterest" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HistoryPrepayment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryPrepaymentPentalty" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HistoryPrincipal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryRental" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HistoryDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HistoryDelinquency" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryLoss" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HistoryCash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryFeePaid" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccruedInterest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RuntimeCurrentPoolBalance" 'PrefixI 'False) (U1 :: Type -> Type))))) | |||||
data PriceResult Source #
Constructors
| PriceResult Valuation PerFace WAL Duration Convexity AccruedInterest [Txn] | |
| AssetPrice Valuation WAL Duration Convexity AccruedInterest | |
| OASResult PriceResult [Valuation] Spread | |
| ZSpread Spread | |
| IrrResult IRR [Txn] |
Instances
| FromJSON PriceResult Source # | |||||
Defined in Types | |||||
| ToJSON PriceResult Source # | |||||
Defined in Types Methods toJSON :: PriceResult -> Value # toEncoding :: PriceResult -> Encoding # toJSONList :: [PriceResult] -> Value # toEncodingList :: [PriceResult] -> Encoding # omitField :: PriceResult -> Bool # | |||||
| Generic PriceResult Source # | |||||
Defined in Types Associated Types
| |||||
| Show PriceResult Source # | |||||
Defined in Types Methods showsPrec :: Int -> PriceResult -> ShowS # show :: PriceResult -> String # showList :: [PriceResult] -> ShowS # | |||||
| Eq PriceResult Source # | |||||
Defined in Types | |||||
| type Rep PriceResult Source # | |||||
Defined in Types | |||||
type DuePremium = Balance Source #
type DateVector = (Date, DatePattern) Source #
Constructors
| CurrentBondBalance | |
| CurrentPoolBalance (Maybe [PoolId]) | |
| CurrentPoolBegBalance (Maybe [PoolId]) | |
| CurrentPoolDefaultedBalance | |
| CumulativePoolDefaultedBalance (Maybe [PoolId]) | Depreciated, use PoolCumCollection |
| CumulativePoolRecoveriesBalance (Maybe [PoolId]) | Depreciated, use PoolCumCollection |
| CumulativeNetLoss (Maybe [PoolId]) | |
| OriginalBondBalance | |
| OriginalBondBalanceOf [BondName] | |
| BondTotalFunding [BondName] | |
| OriginalPoolBalance (Maybe [PoolId]) | |
| DealIssuanceBalance (Maybe [PoolId]) | |
| UseCustomData String | |
| PoolCumCollection [PoolSource] (Maybe [PoolId]) | |
| PoolCumCollectionTill Int [PoolSource] (Maybe [PoolId]) | |
| PoolCurCollection [PoolSource] (Maybe [PoolId]) | |
| PoolCollectionStats Int [PoolSource] (Maybe [PoolId]) | |
| PoolWaSpread (Maybe [PoolId]) | |
| AllAccBalance | |
| AccBalance [AccName] | |
| LedgerBalance [String] | |
| LedgerBalanceBy BookDirection [String] | |
| LedgerTxnAmt [String] (Maybe TxnComment) | |
| ReserveBalance [AccName] | |
| ReserveGap [AccName] | |
| ReserveExcess [AccName] | |
| ReserveGapAt Date [AccName] | |
| ReserveExcessAt Date [AccName] | |
| FutureCurrentPoolBalance (Maybe [PoolId]) | |
| FutureCurrentSchedulePoolBalance (Maybe [PoolId]) | |
| FutureCurrentSchedulePoolBegBalance (Maybe [PoolId]) | |
| PoolScheduleCfPv PricingMethod (Maybe [PoolId]) | |
| FuturePoolScheduleCfPv Date PricingMethod (Maybe [PoolId]) | |
| FutureWaCurrentPoolBalance Date Date (Maybe [PoolId]) | |
| FutureCurrentPoolBegBalance (Maybe [PoolId]) | |
| FutureCurrentBondBalance Date | |
| CurrentBondBalanceOf [BondName] | |
| BondIntPaidAt Date BondName | |
| BondsIntPaidAt Date [BondName] | |
| BondPrinPaidAt Date BondName | |
| BondsPrinPaidAt Date [BondName] | |
| BondBalanceTarget [BondName] | |
| BondBalanceGap BondName | |
| BondBalanceGapAt Date BondName | |
| BondDuePrin [BondName] | |
| BondReturn BondName Balance [TsPoint Amount] | |
| FeePaidAmt [FeeName] | |
| FeeTxnAmt [FeeName] (Maybe TxnComment) | |
| BondTxnAmt [BondName] (Maybe TxnComment) | |
| AccTxnAmt [AccName] (Maybe TxnComment) | |
| FeeTxnAmtBy Date [FeeName] (Maybe TxnComment) | |
| BondTxnAmtBy Date [BondName] (Maybe TxnComment) | |
| AccTxnAmtBy Date [AccName] (Maybe TxnComment) | |
| FeesPaidAt Date [FeeName] | |
| CurrentDueBondInt [BondName] | |
| CurrentDueBondIntAt Int [BondName] | |
| CurrentDueBondIntOverInt [BondName] | |
| CurrentDueBondIntOverIntAt Int [BondName] | |
| CurrentDueBondIntTotal [BondName] | |
| CurrentDueBondIntTotalAt Int [BondName] | |
| CurrentDueFee [FeeName] | |
| LastBondIntPaid [BondName] | |
| LastBondPrinPaid [BondName] | |
| LastFeePaid [FeeName] | |
| LiqCredit [String] | |
| LiqBalance [String] | |
| RateCapNet String | |
| RateSwapNet String | |
| BondBalanceHistory Date Date | |
| PoolCollectionHistory PoolSource Date Date (Maybe [PoolId]) | |
| UnderlyingBondBalance (Maybe [BondName]) | |
| WeightedAvgCurrentPoolBalance Date Date (Maybe [PoolId]) | |
| WeightedAvgCurrentBondBalance Date Date [BondName] | |
| WeightedAvgOriginalPoolBalance Date Date (Maybe [PoolId]) | |
| WeightedAvgOriginalBondBalance Date Date [BondName] | |
| CustomData String Date | |
| DealStatBalance DealStatFields | |
| AmountRequiredForTargetIRR Double BondName | |
| CurrentPoolBorrowerNum (Maybe [PoolId]) | |
| FutureCurrentPoolBorrowerNum Date (Maybe [PoolId]) | |
| ProjCollectPeriodNum | |
| MonthsTillMaturity BondName | |
| DealStatInt DealStatFields | |
| TestRate DealStats Cmp Micro | |
| TestAny Bool [DealStats] | |
| TestAll Bool [DealStats] | |
| TestNot DealStats | |
| IsDealStatus DealStatus | |
| IsMostSenior BondName [BondName] | |
| IsPaidOff [BondName] | |
| IsFeePaidOff [String] | |
| IsLiqSupportPaidOff [String] | |
| IsRateSwapPaidOff [String] | |
| IsOutstanding [BondName] | |
| HasPassedMaturity [BondName] | |
| TriggersStatus DealCycle String | |
| DealStatBool DealStatFields | |
| PoolWaRate (Maybe PoolId) | |
| BondRate BondName | |
| CumulativeNetLossRatio (Maybe [PoolId]) | |
| FutureCurrentBondFactor Date | |
| FutureCurrentPoolFactor Date (Maybe [PoolId]) | |
| BondFactor | |
| BondFactorOf BondName | |
| CumulativePoolDefaultedRate (Maybe [PoolId]) | |
| CumulativePoolDefaultedRateTill Int (Maybe [PoolId]) | |
| PoolFactor (Maybe [PoolId]) | |
| BondWaRate [BondName] | |
| DealStatRate DealStatFields | |
| Factor DealStats Rational | |
| Multiply [DealStats] | |
| Max [DealStats] | |
| Min [DealStats] | |
| Sum [DealStats] | |
| Substract [DealStats] | |
| Subtract [DealStats] | |
| Excess [DealStats] | |
| Avg [DealStats] | |
| AvgRatio [DealStats] | |
| Divide DealStats DealStats | |
| DivideRatio DealStats DealStats | |
| Constant Rational | |
| FloorAndCap DealStats DealStats DealStats | |
| FloorWith DealStats DealStats | |
| FloorWithZero DealStats | |
| CapWith DealStats DealStats | |
| Abs DealStats | |
| Round DealStats (RoundingBy Rational) |
Instances
| FromJSON DealStats Source # | |||||
| ToJSON DealStats Source # | |||||
| Generic DealStats Source # | |||||
Defined in Types Associated Types
| |||||
| Read DealStats Source # | |||||
| Show DealStats Source # | |||||
| Eq DealStats Source # | |||||
| Ord DealStats Source # | |||||
| type Rep DealStats Source # | |||||
Defined in Types type Rep DealStats = D1 ('MetaData "DealStats" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((((((C1 ('MetaCons "CurrentBondBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "CurrentPoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CurrentPoolDefaultedBalance" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CumulativePoolDefaultedBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CumulativePoolRecoveriesBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "CumulativeNetLoss" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "OriginalBondBalance" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "OriginalBondBalanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondTotalFunding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "OriginalPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "DealIssuanceBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: ((C1 ('MetaCons "UseCustomData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PoolCumCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "PoolCumCollectionTill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "PoolCurCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: ((((C1 ('MetaCons "PoolCollectionStats" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "PoolWaSpread" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "AllAccBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])))) :+: ((C1 ('MetaCons "LedgerBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "LedgerBalanceBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: (C1 ('MetaCons "LedgerTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))) :+: C1 ('MetaCons "ReserveBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]))))) :+: (((C1 ('MetaCons "ReserveGap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])) :+: C1 ('MetaCons "ReserveExcess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]))) :+: (C1 ('MetaCons "ReserveGapAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])) :+: C1 ('MetaCons "ReserveExcessAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])))) :+: ((C1 ('MetaCons "FutureCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentSchedulePoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "FutureCurrentSchedulePoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "PoolScheduleCfPv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PricingMethod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))))))) :+: (((((C1 ('MetaCons "FuturePoolScheduleCfPv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PricingMethod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "FutureWaCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "FutureCurrentPoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: ((C1 ('MetaCons "CurrentBondBalanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondIntPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "BondsIntPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondPrinPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))))) :+: (((C1 ('MetaCons "BondsPrinPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondBalanceTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "BondBalanceGap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)) :+: C1 ('MetaCons "BondBalanceGapAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)))) :+: ((C1 ('MetaCons "BondDuePrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondReturn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Amount])))) :+: (C1 ('MetaCons "FeePaidAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])) :+: C1 ('MetaCons "FeeTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))))))) :+: ((((C1 ('MetaCons "BondTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))) :+: C1 ('MetaCons "AccTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: (C1 ('MetaCons "FeeTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: C1 ('MetaCons "BondTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))))) :+: ((C1 ('MetaCons "AccTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: C1 ('MetaCons "FeesPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]))) :+: (C1 ('MetaCons "CurrentDueBondInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))))) :+: (((C1 ('MetaCons "CurrentDueBondIntOverInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntOverIntAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "CurrentDueBondIntTotal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntTotalAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "CurrentDueFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])) :+: C1 ('MetaCons "LastBondIntPaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "LastBondPrinPaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "LastFeePaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])))))))) :+: ((((((C1 ('MetaCons "LiqCredit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "LiqBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: (C1 ('MetaCons "RateCapNet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "RateSwapNet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "BondBalanceHistory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "PoolCollectionHistory" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "UnderlyingBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [BondName]))) :+: C1 ('MetaCons "WeightedAvgCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: (((C1 ('MetaCons "WeightedAvgCurrentBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: C1 ('MetaCons "WeightedAvgOriginalPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "WeightedAvgOriginalBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: C1 ('MetaCons "CustomData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: ((C1 ('MetaCons "DealStatBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "AmountRequiredForTargetIRR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "CurrentPoolBorrowerNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentPoolBorrowerNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: ((((C1 ('MetaCons "ProjCollectPeriodNum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonthsTillMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "DealStatInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "TestRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro))))) :+: ((C1 ('MetaCons "TestAny" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "TestAll" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "TestNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "IsDealStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus))))) :+: (((C1 ('MetaCons "IsMostSenior" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "IsPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "IsFeePaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "IsLiqSupportPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :+: ((C1 ('MetaCons "IsRateSwapPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "IsOutstanding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "HasPassedMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "TriggersStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealCycle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))) :+: (((((C1 ('MetaCons "DealStatBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "PoolWaRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PoolId)))) :+: (C1 ('MetaCons "BondRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)) :+: C1 ('MetaCons "CumulativeNetLossRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: ((C1 ('MetaCons "FutureCurrentBondFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "FutureCurrentPoolFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "BondFactor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BondFactorOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))))) :+: (((C1 ('MetaCons "CumulativePoolDefaultedRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CumulativePoolDefaultedRateTill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "PoolFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "BondWaRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "DealStatRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "Factor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :+: (C1 ('MetaCons "Multiply" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Max" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))))) :+: ((((C1 ('MetaCons "Min" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Sum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "Substract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Subtract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))) :+: ((C1 ('MetaCons "Excess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Avg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "AvgRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Divide" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))))) :+: (((C1 ('MetaCons "DivideRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Constant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :+: (C1 ('MetaCons "FloorAndCap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "FloorWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))) :+: ((C1 ('MetaCons "FloorWithZero" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "CapWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: (C1 ('MetaCons "Abs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Round" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RoundingBy Rational)))))))))) | |||||
data PricingMethod Source #
pricing methods for bonds
Constructors
| BalanceFactor Rate Rate |
|
| BalanceFactor2 Rate Rate Rate |
|
| DefaultedBalance Rate |
|
| PV IRate Rate | discount factor, recovery pct on default |
| PVCurve Ts |
|
| PvRate IRate |
|
| PvWal Ts | |
| PvByRef DealStats |
|
| Custom Rate | custom amount |
Instances
| FromJSON PricingMethod Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser PricingMethod # parseJSONList :: Value -> Parser [PricingMethod] # | |||||
| ToJSON PricingMethod Source # | |||||
Defined in Types Methods toJSON :: PricingMethod -> Value # toEncoding :: PricingMethod -> Encoding # toJSONList :: [PricingMethod] -> Value # toEncodingList :: [PricingMethod] -> Encoding # omitField :: PricingMethod -> Bool # | |||||
| Generic PricingMethod Source # | |||||
Defined in Types Associated Types
| |||||
| Read PricingMethod Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS PricingMethod # readList :: ReadS [PricingMethod] # | |||||
| Show PricingMethod Source # | |||||
Defined in Types Methods showsPrec :: Int -> PricingMethod -> ShowS # show :: PricingMethod -> String # showList :: [PricingMethod] -> ShowS # | |||||
| Eq PricingMethod Source # | |||||
Defined in Types Methods (==) :: PricingMethod -> PricingMethod -> Bool # (/=) :: PricingMethod -> PricingMethod -> Bool # | |||||
| Ord PricingMethod Source # | |||||
Defined in Types Methods compare :: PricingMethod -> PricingMethod -> Ordering # (<) :: PricingMethod -> PricingMethod -> Bool # (<=) :: PricingMethod -> PricingMethod -> Bool # (>) :: PricingMethod -> PricingMethod -> Bool # (>=) :: PricingMethod -> PricingMethod -> Bool # max :: PricingMethod -> PricingMethod -> PricingMethod # min :: PricingMethod -> PricingMethod -> PricingMethod # | |||||
| type Rep PricingMethod Source # | |||||
Defined in Types type Rep PricingMethod = D1 ('MetaData "PricingMethod" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "BalanceFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "BalanceFactor2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))) :+: (C1 ('MetaCons "DefaultedBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PV" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))) :+: ((C1 ('MetaCons "PVCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: C1 ('MetaCons "PvRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate))) :+: (C1 ('MetaCons "PvWal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: (C1 ('MetaCons "PvByRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))))) | |||||
data CustomDataType Source #
Constructors
| CustomConstant Rational | |
| CustomCurve Ts | |
| CustomDS DealStats |
Instances
| FromJSON CustomDataType Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser CustomDataType # parseJSONList :: Value -> Parser [CustomDataType] # | |||||
| ToJSON CustomDataType Source # | |||||
Defined in Types Methods toJSON :: CustomDataType -> Value # toEncoding :: CustomDataType -> Encoding # toJSONList :: [CustomDataType] -> Value # toEncodingList :: [CustomDataType] -> Encoding # omitField :: CustomDataType -> Bool # | |||||
| Generic CustomDataType Source # | |||||
Defined in Types Associated Types
Methods from :: CustomDataType -> Rep CustomDataType x # to :: Rep CustomDataType x -> CustomDataType # | |||||
| Read CustomDataType Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS CustomDataType # readList :: ReadS [CustomDataType] # | |||||
| Show CustomDataType Source # | |||||
Defined in Types Methods showsPrec :: Int -> CustomDataType -> ShowS # show :: CustomDataType -> String # showList :: [CustomDataType] -> ShowS # | |||||
| Eq CustomDataType Source # | |||||
Defined in Types Methods (==) :: CustomDataType -> CustomDataType -> Bool # (/=) :: CustomDataType -> CustomDataType -> Bool # | |||||
| Ord CustomDataType Source # | |||||
Defined in Types Methods compare :: CustomDataType -> CustomDataType -> Ordering # (<) :: CustomDataType -> CustomDataType -> Bool # (<=) :: CustomDataType -> CustomDataType -> Bool # (>) :: CustomDataType -> CustomDataType -> Bool # (>=) :: CustomDataType -> CustomDataType -> Bool # max :: CustomDataType -> CustomDataType -> CustomDataType # min :: CustomDataType -> CustomDataType -> CustomDataType # | |||||
| type Rep CustomDataType Source # | |||||
Defined in Types type Rep CustomDataType = D1 ('MetaData "CustomDataType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "CustomConstant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: (C1 ('MetaCons "CustomCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: C1 ('MetaCons "CustomDS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))) | |||||
data ResultComponent Source #
Constructors
| CallAt Date | the date when deal called |
| DealStatusChangeTo Date DealStatus DealStatus String | record when & why status changed |
| BondOutstanding String Balance Balance | when deal ends,calculate oustanding principal balance |
| BondOutstandingInt String Balance Balance | when deal ends,calculate oustanding interest due |
| InspectBal Date DealStats Balance | A bal value from inspection |
| InspectInt Date DealStats Int | A int value from inspection |
| InspectRate Date DealStats Micro | A rate value from inspection |
| InspectBool Date DealStats Bool | A bool value from inspection |
| RunningWaterfall Date ActionWhen | running waterfall at a date |
| FinancialReport StartDate EndDate BalanceSheetReport CashflowReport | |
| InspectWaterfall Date (Maybe String) [DealStats] [String] | |
| ErrorMsg String | |
| WarningMsg String | |
| EndRun (Maybe Date) String | end of run with a message | SnapshotCashflow Date String CashFlowFrame |
Instances
| FromJSON ResultComponent Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser ResultComponent # parseJSONList :: Value -> Parser [ResultComponent] # | |||||
| ToJSON ResultComponent Source # | |||||
Defined in Types Methods toJSON :: ResultComponent -> Value # toEncoding :: ResultComponent -> Encoding # toJSONList :: [ResultComponent] -> Value # toEncodingList :: [ResultComponent] -> Encoding # omitField :: ResultComponent -> Bool # | |||||
| Generic ResultComponent Source # | |||||
Defined in Types Associated Types
Methods from :: ResultComponent -> Rep ResultComponent x # to :: Rep ResultComponent x -> ResultComponent # | |||||
| Show ResultComponent Source # | |||||
Defined in Types Methods showsPrec :: Int -> ResultComponent -> ShowS # show :: ResultComponent -> String # showList :: [ResultComponent] -> ShowS # | |||||
| Eq ResultComponent Source # | |||||
Defined in Types Methods (==) :: ResultComponent -> ResultComponent -> Bool # (/=) :: ResultComponent -> ResultComponent -> Bool # | |||||
| type Rep ResultComponent Source # | |||||
Defined in Types type Rep ResultComponent = D1 ('MetaData "ResultComponent" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "CallAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "DealStatusChangeTo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "BondOutstanding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))))) :+: ((C1 ('MetaCons "BondOutstandingInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: C1 ('MetaCons "InspectBal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: (C1 ('MetaCons "InspectInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: C1 ('MetaCons "InspectRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro)))))) :+: ((C1 ('MetaCons "InspectBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "RunningWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ActionWhen)) :+: C1 ('MetaCons "FinancialReport" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartDate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndDate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BalanceSheetReport) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CashflowReport))))) :+: ((C1 ('MetaCons "InspectWaterfall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: C1 ('MetaCons "ErrorMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "WarningMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "EndRun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))) | |||||
data DealStatType Source #
Constructors
| RtnBalance | |
| RtnRate | |
| RtnBool | |
| RtnInt |
Instances
| Generic DealStatType Source # | |||||
Defined in Types Associated Types
| |||||
| Read DealStatType Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS DealStatType # readList :: ReadS [DealStatType] # | |||||
| Show DealStatType Source # | |||||
Defined in Types Methods showsPrec :: Int -> DealStatType -> ShowS # show :: DealStatType -> String # showList :: [DealStatType] -> ShowS # | |||||
| Eq DealStatType Source # | |||||
Defined in Types | |||||
| Ord DealStatType Source # | |||||
Defined in Types Methods compare :: DealStatType -> DealStatType -> Ordering # (<) :: DealStatType -> DealStatType -> Bool # (<=) :: DealStatType -> DealStatType -> Bool # (>) :: DealStatType -> DealStatType -> Bool # (>=) :: DealStatType -> DealStatType -> Bool # max :: DealStatType -> DealStatType -> DealStatType # min :: DealStatType -> DealStatType -> DealStatType # | |||||
| type Rep DealStatType Source # | |||||
Defined in Types type Rep DealStatType = D1 ('MetaData "DealStatType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "RtnBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtnRate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RtnBool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtnInt" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
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))))) | |||||
data DealStatFields Source #
different types of deal stats
Constructors
| PoolCollectedPeriod | |
| BondPaidPeriod |
Instances
| FromJSON DealStatFields Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser DealStatFields # parseJSONList :: Value -> Parser [DealStatFields] # | |||||
| FromJSONKey DealStatFields Source # | |||||
Defined in Deal.DealBase | |||||
| ToJSON DealStatFields Source # | |||||
Defined in Types Methods toJSON :: DealStatFields -> Value # toEncoding :: DealStatFields -> Encoding # toJSONList :: [DealStatFields] -> Value # toEncodingList :: [DealStatFields] -> Encoding # omitField :: DealStatFields -> Bool # | |||||
| ToJSONKey DealStatFields Source # | |||||
Defined in Deal.DealBase | |||||
| Generic DealStatFields Source # | |||||
Defined in Types Associated Types
Methods from :: DealStatFields -> Rep DealStatFields x # to :: Rep DealStatFields x -> DealStatFields # | |||||
| Read DealStatFields Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS DealStatFields # readList :: ReadS [DealStatFields] # | |||||
| Show DealStatFields Source # | |||||
Defined in Types Methods showsPrec :: Int -> DealStatFields -> ShowS # show :: DealStatFields -> String # showList :: [DealStatFields] -> ShowS # | |||||
| Eq DealStatFields Source # | |||||
Defined in Types Methods (==) :: DealStatFields -> DealStatFields -> Bool # (/=) :: DealStatFields -> DealStatFields -> Bool # | |||||
| Ord DealStatFields Source # | |||||
Defined in Types Methods compare :: DealStatFields -> DealStatFields -> Ordering # (<) :: DealStatFields -> DealStatFields -> Bool # (<=) :: DealStatFields -> DealStatFields -> Bool # (>) :: DealStatFields -> DealStatFields -> Bool # (>=) :: DealStatFields -> DealStatFields -> Bool # max :: DealStatFields -> DealStatFields -> DealStatFields # min :: DealStatFields -> DealStatFields -> DealStatFields # | |||||
| type Rep DealStatFields Source # | |||||
getPriceValue :: PriceResult -> Balance Source #
Constructors
| ByProRata | |
| BySequential |
data BondPricingMethod Source #
condition which can be evaluated to a boolean value
Constructors
| BondBalanceFactor Rate | |
| PvBondByRate Rate | |
| PvBondByCurve Ts |
Instances
| FromJSON BondPricingMethod Source # | |||||
Defined in Types Methods parseJSON :: Value -> Parser BondPricingMethod # parseJSONList :: Value -> Parser [BondPricingMethod] # | |||||
| ToJSON BondPricingMethod Source # | |||||
Defined in Types Methods toJSON :: BondPricingMethod -> Value # toEncoding :: BondPricingMethod -> Encoding # toJSONList :: [BondPricingMethod] -> Value # toEncodingList :: [BondPricingMethod] -> Encoding # omitField :: BondPricingMethod -> Bool # | |||||
| Generic BondPricingMethod Source # | |||||
Defined in Types Associated Types
Methods from :: BondPricingMethod -> Rep BondPricingMethod x # to :: Rep BondPricingMethod x -> BondPricingMethod # | |||||
| Read BondPricingMethod Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS BondPricingMethod # readList :: ReadS [BondPricingMethod] # | |||||
| Show BondPricingMethod Source # | |||||
Defined in Types Methods showsPrec :: Int -> BondPricingMethod -> ShowS # show :: BondPricingMethod -> String # showList :: [BondPricingMethod] -> ShowS # | |||||
| Eq BondPricingMethod Source # | |||||
Defined in Types Methods (==) :: BondPricingMethod -> BondPricingMethod -> Bool # (/=) :: BondPricingMethod -> BondPricingMethod -> Bool # | |||||
| Ord BondPricingMethod Source # | |||||
Defined in Types Methods compare :: BondPricingMethod -> BondPricingMethod -> Ordering # (<) :: BondPricingMethod -> BondPricingMethod -> Bool # (<=) :: BondPricingMethod -> BondPricingMethod -> Bool # (>) :: BondPricingMethod -> BondPricingMethod -> Bool # (>=) :: BondPricingMethod -> BondPricingMethod -> Bool # max :: BondPricingMethod -> BondPricingMethod -> BondPricingMethod # min :: BondPricingMethod -> BondPricingMethod -> BondPricingMethod # | |||||
| type Rep BondPricingMethod Source # | |||||
Defined in Types type Rep BondPricingMethod = D1 ('MetaData "BondPricingMethod" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BondBalanceFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: (C1 ('MetaCons "PvBondByRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PvBondByCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)))) | |||||
data InvestorAction Source #
Instances
| Generic InvestorAction Source # | |||||
Defined in Types Associated Types
Methods from :: InvestorAction -> Rep InvestorAction x # to :: Rep InvestorAction x -> InvestorAction # | |||||
| Read InvestorAction Source # | |||||
Defined in Types Methods readsPrec :: Int -> ReadS InvestorAction # readList :: ReadS [InvestorAction] # | |||||
| Show InvestorAction Source # | |||||
Defined in Types Methods showsPrec :: Int -> InvestorAction -> ShowS # show :: InvestorAction -> String # showList :: [InvestorAction] -> ShowS # | |||||
| Eq InvestorAction Source # | |||||
Defined in Types Methods (==) :: InvestorAction -> InvestorAction -> Bool # (/=) :: InvestorAction -> InvestorAction -> Bool # | |||||
| Ord InvestorAction Source # | |||||
Defined in Types Methods compare :: InvestorAction -> InvestorAction -> Ordering # (<) :: InvestorAction -> InvestorAction -> Bool # (<=) :: InvestorAction -> InvestorAction -> Bool # (>) :: InvestorAction -> InvestorAction -> Bool # (>=) :: InvestorAction -> InvestorAction -> Bool # max :: InvestorAction -> InvestorAction -> InvestorAction # min :: InvestorAction -> InvestorAction -> InvestorAction # | |||||
| type Rep InvestorAction Source # | |||||
_BondTxn :: Prism' Txn (Date, Balance, Interest, Principal, IRate, Cash, DueInt, DueIoI, Maybe Float, TxnComment) Source #
_IrrResult :: Prism' PriceResult (IRR, [Txn]) Source #
Orphan instances
| FromJSON i => FromJSON (DecimalRaw i) Source # | |
Methods parseJSON :: Value -> Parser (DecimalRaw i) # parseJSONList :: Value -> Parser [DecimalRaw i] # omittedField :: Maybe (DecimalRaw i) # | |
| ToJSON i => ToJSON (DecimalRaw i) Source # | |
Methods toJSON :: DecimalRaw i -> Value # toEncoding :: DecimalRaw i -> Encoding # toJSONList :: [DecimalRaw i] -> Value # toEncodingList :: [DecimalRaw i] -> Encoding # omitField :: DecimalRaw i -> Bool # | |