Safe Haskell | None |
---|---|
Language | Haskell2010 |
AssetClass.AssetBase
Contents
Synopsis
- data Installment
- data Lease
- data OriginalInfo
- = MortgageOriginalInfo { }
- | LoanOriginalInfo {
- originBalance :: Balance
- originRate :: RateType
- originTerm :: Int
- period :: Period
- startDate :: Date
- prinType :: AmortPlan
- obligor :: Maybe Obligor
- | LeaseInfo { }
- | FixedAssetInfo {
- startDate :: Date
- originBalance :: Balance
- residualBalance :: Balance
- originTerm :: Int
- period :: Period
- accRule :: AmortRule
- capacity :: Capacity
- | ReceivableInfo { }
- data Status
- data LeaseStepUp
- data AccrualPeriod = AccrualPeriod Date DailyRate
- data PrepayPenaltyType
- data AmortPlan
- data Loan
- data Mortgage
- data AssetUnion
- = MO Mortgage
- | LO Loan
- | IL Installment
- | LS Lease
- | FA FixedAsset
- | RE Receivable
- | PF ProjectedCashflow
- data MixedAsset
- = MixedPool (Map String [AssetUnion])
- | DUMMY2
- data FixedAsset
- data AmortRule
- data Capacity
- = FixedCapacity Balance
- | CapacityByTerm [(Int, Balance)]
- data AssociateExp
- data AssociateIncome
- data ReceivableFeeType
- data Receivable
- data ProjectedCashflow
- = ProjectedFlowFixed CashFlowFrame DatePattern
- | ProjectedFlowMixFloater CashFlowFrame DatePattern FixRatePortion [FloatRatePortion]
- data Obligor = Obligor {
- obligorId :: String
- obligorTag :: [String]
- obligorFields :: Map String (Either String Double)
- data LeaseRateCalc
- = ByDayRate DailyRate DatePattern
- | ByPeriodRental Balance Period
- calcAssetPrinInt :: AmortPlan -> Balance -> IRate -> Int -> Int -> (Balance, Int) -> (InterestAmount, PrincipalAmount)
- calcPmt :: Balance -> IRate -> Int -> Amount
Documentation
data Installment Source #
Constructors
Installment OriginalInfo Balance RemainTerms Status | |
Dummy |
Instances
Constructors
RegularLease OriginalInfo Balance RemainTerms Status | |
StepUpLease OriginalInfo LeaseStepUp Balance RemainTerms Status |
Instances
Asset Lease Source # | |||||
Defined in AssetClass.Lease Methods calcCashflow :: Lease -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: Lease -> Balance Source # getOriginBal :: Lease -> Balance Source # getOriginRate :: Lease -> IRate Source # getCurrentRate :: Lease -> IRate Source # getOriginDate :: Lease -> Date Source # getOriginInfo :: Lease -> OriginalInfo Source # isDefaulted :: Lease -> Bool Source # getPaymentDates :: Lease -> Int -> [Date] Source # getRemainTerms :: Lease -> Int Source # getRemainDates :: Lease -> [Date] Source # getTotalTerms :: Lease -> Int Source # getPastTerms :: Lease -> Int Source # projCashflow :: Lease -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: Lease -> Int Source # splitWith :: Lease -> [Rate] -> [Lease] Source # updateOriginDate :: Lease -> Date -> Lease Source # resetToOrig :: Lease -> Lease Source # getLastInterestPaymentDate :: Lease -> Maybe Date Source # calcAccruedInterest :: Lease -> Date -> Balance Source # calcAlignDate :: Lease -> Date -> Date Source # getObligor :: Lease -> Maybe Obligor Source # getObligorTags :: Lease -> Set String Source # getObligorId :: Lease -> Maybe String Source # getObligorFields :: Lease -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate Lease Source # | |||||
FromJSON Lease Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Lease Source # | |||||
Generic Lease Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Lease Source # | |||||
Eq Lease Source # | |||||
Ord Lease Source # | |||||
type Rep Lease Source # | |||||
Defined in AssetClass.AssetBase type Rep Lease = D1 ('MetaData "Lease" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "RegularLease" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemainTerms) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status))) :+: C1 ('MetaCons "StepUpLease" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LeaseStepUp)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemainTerms) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status))))) |
data OriginalInfo Source #
Constructors
MortgageOriginalInfo | |
Fields
| |
LoanOriginalInfo | |
Fields
| |
LeaseInfo | |
Fields
| |
FixedAssetInfo | |
Fields
| |
ReceivableInfo | |
Fields
|
Instances
FromJSON OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: OriginalInfo -> Value # toEncoding :: OriginalInfo -> Encoding # toJSONList :: [OriginalInfo] -> Value # toEncodingList :: [OriginalInfo] -> Encoding # omitField :: OriginalInfo -> Bool # | |||||
Generic OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> OriginalInfo -> ShowS # show :: OriginalInfo -> String # showList :: [OriginalInfo] -> ShowS # | |||||
Eq OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: OriginalInfo -> OriginalInfo -> Ordering # (<) :: OriginalInfo -> OriginalInfo -> Bool # (<=) :: OriginalInfo -> OriginalInfo -> Bool # (>) :: OriginalInfo -> OriginalInfo -> Bool # (>=) :: OriginalInfo -> OriginalInfo -> Bool # max :: OriginalInfo -> OriginalInfo -> OriginalInfo # min :: OriginalInfo -> OriginalInfo -> OriginalInfo # | |||||
ToSchema OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy OriginalInfo -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep OriginalInfo Source # | |||||
Defined in AssetClass.AssetBase type Rep OriginalInfo = D1 ('MetaData "OriginalInfo" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "MortgageOriginalInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "originBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Just "originRate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RateType)) :*: (S1 ('MetaSel ('Just "originTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "period") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Period))) :*: ((S1 ('MetaSel ('Just "startDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Just "prinType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AmortPlan)) :*: (S1 ('MetaSel ('Just "prepaymentPenalty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PrepayPenaltyType)) :*: S1 ('MetaSel ('Just "obligor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Obligor))))) :+: C1 ('MetaCons "LoanOriginalInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "originBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: (S1 ('MetaSel ('Just "originRate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RateType) :*: S1 ('MetaSel ('Just "originTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "period") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Period) :*: S1 ('MetaSel ('Just "startDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :*: (S1 ('MetaSel ('Just "prinType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AmortPlan) :*: S1 ('MetaSel ('Just "obligor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Obligor)))))) :+: (C1 ('MetaCons "LeaseInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "startDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Just "originTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "originRental") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LeaseRateCalc) :*: S1 ('MetaSel ('Just "obligor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Obligor)))) :+: (C1 ('MetaCons "FixedAssetInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "startDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Just "originBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Just "residualBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Just "originTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "period") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Period)) :*: (S1 ('MetaSel ('Just "accRule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AmortRule) :*: S1 ('MetaSel ('Just "capacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Capacity)))) :+: C1 ('MetaCons "ReceivableInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "startDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Just "originBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Just "originAdvance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: (S1 ('MetaSel ('Just "dueDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Just "feeType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ReceivableFeeType)) :*: S1 ('MetaSel ('Just "obligor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Obligor)))))))) |
Instances
FromJSON Status Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Status Source # | |||||
Generic Status Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Status Source # | Delinquency (Maybe Int) | Extended (Maybe T.Day) | ||||
Eq Status Source # | |||||
Ord Status Source # | |||||
ToSchema Status Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Status -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep Status Source # | |||||
Defined in AssetClass.AssetBase type Rep Status = D1 ('MetaData "Status" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Current" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Defaulted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)))) |
data LeaseStepUp Source #
Constructors
FlatRate Rate | |
ByRateCurve [Rate] | |
ByFlatAmount Balance | |
ByAmountCurve [Balance] |
Instances
FromJSON LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: LeaseStepUp -> Value # toEncoding :: LeaseStepUp -> Encoding # toJSONList :: [LeaseStepUp] -> Value # toEncodingList :: [LeaseStepUp] -> Encoding # omitField :: LeaseStepUp -> Bool # | |||||
Generic LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> LeaseStepUp -> ShowS # show :: LeaseStepUp -> String # showList :: [LeaseStepUp] -> ShowS # | |||||
Eq LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: LeaseStepUp -> LeaseStepUp -> Ordering # (<) :: LeaseStepUp -> LeaseStepUp -> Bool # (<=) :: LeaseStepUp -> LeaseStepUp -> Bool # (>) :: LeaseStepUp -> LeaseStepUp -> Bool # (>=) :: LeaseStepUp -> LeaseStepUp -> Bool # max :: LeaseStepUp -> LeaseStepUp -> LeaseStepUp # min :: LeaseStepUp -> LeaseStepUp -> LeaseStepUp # | |||||
type Rep LeaseStepUp Source # | |||||
Defined in AssetClass.AssetBase type Rep LeaseStepUp = D1 ('MetaData "LeaseStepUp" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "FlatRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "ByRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rate]))) :+: (C1 ('MetaCons "ByFlatAmount" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "ByAmountCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Balance])))) |
data AccrualPeriod Source #
Constructors
AccrualPeriod Date DailyRate |
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 # | |||||
Generic AccrualPeriod Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show AccrualPeriod Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> AccrualPeriod -> ShowS # show :: AccrualPeriod -> String # showList :: [AccrualPeriod] -> ShowS # | |||||
Eq AccrualPeriod Source # | |||||
Defined in AssetClass.AssetBase Methods (==) :: AccrualPeriod -> AccrualPeriod -> Bool # (/=) :: AccrualPeriod -> AccrualPeriod -> Bool # | |||||
Ord AccrualPeriod Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: AccrualPeriod -> AccrualPeriod -> Ordering # (<) :: AccrualPeriod -> AccrualPeriod -> Bool # (<=) :: AccrualPeriod -> AccrualPeriod -> Bool # (>) :: AccrualPeriod -> AccrualPeriod -> Bool # (>=) :: AccrualPeriod -> AccrualPeriod -> Bool # max :: AccrualPeriod -> AccrualPeriod -> AccrualPeriod # min :: AccrualPeriod -> AccrualPeriod -> AccrualPeriod # | |||||
type Rep AccrualPeriod Source # | |||||
Defined in AssetClass.AssetBase |
data PrepayPenaltyType Source #
Constructors
ByTerm Int Rate Rate | using penalty rate 1 if period use penalty rate 2 if period Int |
FixAmount Balance (Maybe Int) | fixed penalty fee if any prepayment, or it only applies if period < Int |
FixPct Rate (Maybe Int) | fixed percentage penalty fee as percentage of prepayment, or it only applies if period < Int |
Sliding Rate Rate | starting with Rate1 at period 1 then decrease by step by rate2 |
StepDown [(Int, Rate)] | first tuple (n,r) ,first n periods use penalty rate r , then next n periods use pentaly rate in next tuple | NMonthInterest Int |
Instances
FromJSON PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Methods parseJSON :: Value -> Parser PrepayPenaltyType # parseJSONList :: Value -> Parser [PrepayPenaltyType] # | |||||
ToJSON PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: PrepayPenaltyType -> Value # toEncoding :: PrepayPenaltyType -> Encoding # toJSONList :: [PrepayPenaltyType] -> Value # toEncodingList :: [PrepayPenaltyType] -> Encoding # omitField :: PrepayPenaltyType -> Bool # | |||||
Generic PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Associated Types
Methods from :: PrepayPenaltyType -> Rep PrepayPenaltyType x # to :: Rep PrepayPenaltyType x -> PrepayPenaltyType # | |||||
Show PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> PrepayPenaltyType -> ShowS # show :: PrepayPenaltyType -> String # showList :: [PrepayPenaltyType] -> ShowS # | |||||
Eq PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Methods (==) :: PrepayPenaltyType -> PrepayPenaltyType -> Bool # (/=) :: PrepayPenaltyType -> PrepayPenaltyType -> Bool # | |||||
Ord PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: PrepayPenaltyType -> PrepayPenaltyType -> Ordering # (<) :: PrepayPenaltyType -> PrepayPenaltyType -> Bool # (<=) :: PrepayPenaltyType -> PrepayPenaltyType -> Bool # (>) :: PrepayPenaltyType -> PrepayPenaltyType -> Bool # (>=) :: PrepayPenaltyType -> PrepayPenaltyType -> Bool # max :: PrepayPenaltyType -> PrepayPenaltyType -> PrepayPenaltyType # min :: PrepayPenaltyType -> PrepayPenaltyType -> PrepayPenaltyType # | |||||
ToSchema PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy PrepayPenaltyType -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep PrepayPenaltyType Source # | |||||
Defined in AssetClass.AssetBase type Rep PrepayPenaltyType = D1 ('MetaData "PrepayPenaltyType" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "ByTerm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))) :+: C1 ('MetaCons "FixAmount" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :+: (C1 ('MetaCons "FixPct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :+: (C1 ('MetaCons "Sliding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "StepDown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Rate)]))))) |
Constructors
Level | for mortgage / french system -> fixed payment each period which consist of increasing princial and decreasing interest. |
Even | for linear mortgage -> evenly distributed principal repayment |
I_P | interest only and principal due at last payment |
F_P | fee based |
PO_FirstN Int | 0 fee for first N period |
IO_FirstN Int AmortPlan | interest only for first N period |
NO_FirstN Int AmortPlan | non payment during first N period |
ScheduleRepayment Ts (Maybe DatePattern) | custom principal follow |
Balloon Int | balloon payment with period N |
Instances
FromJSON AmortPlan Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON AmortPlan Source # | |||||
Generic AmortPlan Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show AmortPlan Source # | |||||
Eq AmortPlan Source # | |||||
Ord AmortPlan Source # | |||||
ToSchema AmortPlan Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy AmortPlan -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep AmortPlan Source # | |||||
Defined in AssetClass.AssetBase type Rep AmortPlan = D1 ('MetaData "AmortPlan" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "Level" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Even" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "I_P" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "F_P" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PO_FirstN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "IO_FirstN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AmortPlan))) :+: (C1 ('MetaCons "NO_FirstN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AmortPlan)) :+: (C1 ('MetaCons "ScheduleRepayment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DatePattern))) :+: C1 ('MetaCons "Balloon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))) |
Constructors
PersonalLoan OriginalInfo Balance IRate RemainTerms Status | |
DUMMY |
Instances
Asset Loan Source # | |||||
Defined in AssetClass.Loan Methods calcCashflow :: Loan -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: Loan -> Balance Source # getOriginBal :: Loan -> Balance Source # getOriginRate :: Loan -> IRate Source # getCurrentRate :: Loan -> IRate Source # getOriginDate :: Loan -> Date Source # getOriginInfo :: Loan -> OriginalInfo Source # isDefaulted :: Loan -> Bool Source # getPaymentDates :: Loan -> Int -> [Date] Source # getRemainTerms :: Loan -> Int Source # getRemainDates :: Loan -> [Date] Source # getTotalTerms :: Loan -> Int Source # getPastTerms :: Loan -> Int Source # projCashflow :: Loan -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: Loan -> Int Source # splitWith :: Loan -> [Rate] -> [Loan] Source # updateOriginDate :: Loan -> Date -> Loan Source # resetToOrig :: Loan -> Loan Source # getLastInterestPaymentDate :: Loan -> Maybe Date Source # calcAccruedInterest :: Loan -> Date -> Balance Source # calcAlignDate :: Loan -> Date -> Date Source # getObligor :: Loan -> Maybe Obligor Source # getObligorTags :: Loan -> Set String Source # getObligorId :: Loan -> Maybe String Source # getObligorFields :: Loan -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate Loan Source # | |||||
FromJSON Loan Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Loan Source # | |||||
Generic Loan Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Loan Source # | |||||
Eq Loan Source # | |||||
Ord Loan Source # | |||||
type Rep Loan Source # | |||||
Defined in AssetClass.AssetBase type Rep Loan = D1 ('MetaData "Loan" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PersonalLoan" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemainTerms) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :+: C1 ('MetaCons "DUMMY" 'PrefixI 'False) (U1 :: Type -> Type)) |
Constructors
Mortgage OriginalInfo Balance IRate RemainTerms (Maybe BorrowerNum) Status | |
AdjustRateMortgage OriginalInfo ARM Balance IRate RemainTerms (Maybe BorrowerNum) Status | |
ScheduleMortgageFlow Date [TsRow] DatePattern |
Instances
Asset Mortgage Source # | |||||
Defined in AssetClass.Mortgage Methods calcCashflow :: Mortgage -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: Mortgage -> Balance Source # getOriginBal :: Mortgage -> Balance Source # getOriginRate :: Mortgage -> IRate Source # getCurrentRate :: Mortgage -> IRate Source # getOriginDate :: Mortgage -> Date Source # getOriginInfo :: Mortgage -> OriginalInfo Source # isDefaulted :: Mortgage -> Bool Source # getPaymentDates :: Mortgage -> Int -> [Date] Source # getRemainTerms :: Mortgage -> Int Source # getRemainDates :: Mortgage -> [Date] Source # getTotalTerms :: Mortgage -> Int Source # getPastTerms :: Mortgage -> Int Source # projCashflow :: Mortgage -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: Mortgage -> Int Source # splitWith :: Mortgage -> [Rate] -> [Mortgage] Source # updateOriginDate :: Mortgage -> Date -> Mortgage Source # resetToOrig :: Mortgage -> Mortgage Source # getLastInterestPaymentDate :: Mortgage -> Maybe Date Source # calcAccruedInterest :: Mortgage -> Date -> Balance Source # calcAlignDate :: Mortgage -> Date -> Date Source # getObligor :: Mortgage -> Maybe Obligor Source # getObligorTags :: Mortgage -> Set String Source # getObligorId :: Mortgage -> Maybe String Source # getObligorFields :: Mortgage -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate Mortgage Source # | |||||
FromJSON Mortgage Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Mortgage Source # | |||||
Generic Mortgage Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Mortgage Source # | |||||
Eq Mortgage Source # | |||||
Ord Mortgage Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToSchema Mortgage Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Mortgage -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep Mortgage Source # | |||||
Defined in AssetClass.AssetBase type Rep Mortgage = D1 ('MetaData "Mortgage" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Mortgage" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemainTerms) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BorrowerNum)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :+: (C1 ('MetaCons "AdjustRateMortgage" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ARM) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemainTerms)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BorrowerNum)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :+: C1 ('MetaCons "ScheduleMortgageFlow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsRow]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))))) |
data AssetUnion Source #
Constructors
MO Mortgage | |
LO Loan | |
IL Installment | |
LS Lease | |
FA FixedAsset | |
RE Receivable | |
PF ProjectedCashflow |
Instances
Asset AssetUnion Source # | |||||
Defined in AssetClass.MixedAsset Methods calcCashflow :: AssetUnion -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: AssetUnion -> Balance Source # getOriginBal :: AssetUnion -> Balance Source # getOriginRate :: AssetUnion -> IRate Source # getCurrentRate :: AssetUnion -> IRate Source # getOriginDate :: AssetUnion -> Date Source # getOriginInfo :: AssetUnion -> OriginalInfo Source # isDefaulted :: AssetUnion -> Bool Source # getPaymentDates :: AssetUnion -> Int -> [Date] Source # getRemainTerms :: AssetUnion -> Int Source # getRemainDates :: AssetUnion -> [Date] Source # getTotalTerms :: AssetUnion -> Int Source # getPastTerms :: AssetUnion -> Int Source # projCashflow :: AssetUnion -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: AssetUnion -> Int Source # splitWith :: AssetUnion -> [Rate] -> [AssetUnion] Source # updateOriginDate :: AssetUnion -> Date -> AssetUnion Source # resetToOrig :: AssetUnion -> AssetUnion Source # getLastInterestPaymentDate :: AssetUnion -> Maybe Date Source # calcAccruedInterest :: AssetUnion -> Date -> Balance Source # calcAlignDate :: AssetUnion -> Date -> Date Source # getObligor :: AssetUnion -> Maybe Obligor Source # getObligorTags :: AssetUnion -> Set String Source # getObligorId :: AssetUnion -> Maybe String Source # getObligorFields :: AssetUnion -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate AssetUnion Source # | |||||
Defined in AssetClass.AssetBase Methods isAdjustbleRate :: AssetUnion -> Bool Source # getIndex :: AssetUnion -> Maybe Index Source # getIndexes :: AssetUnion -> Maybe [Index] Source # getResetDates :: AssetUnion -> Dates Source # | |||||
FromJSON AssetUnion Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON AssetUnion Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: AssetUnion -> Value # toEncoding :: AssetUnion -> Encoding # toJSONList :: [AssetUnion] -> Value # toEncodingList :: [AssetUnion] -> Encoding # omitField :: AssetUnion -> Bool # | |||||
Generic AssetUnion Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show AssetUnion Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> AssetUnion -> ShowS # show :: AssetUnion -> String # showList :: [AssetUnion] -> ShowS # | |||||
Eq AssetUnion Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord AssetUnion Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: AssetUnion -> AssetUnion -> Ordering # (<) :: AssetUnion -> AssetUnion -> Bool # (<=) :: AssetUnion -> AssetUnion -> Bool # (>) :: AssetUnion -> AssetUnion -> Bool # (>=) :: AssetUnion -> AssetUnion -> Bool # max :: AssetUnion -> AssetUnion -> AssetUnion # min :: AssetUnion -> AssetUnion -> AssetUnion # | |||||
type Rep AssetUnion Source # | |||||
Defined in AssetClass.AssetBase type Rep AssetUnion = D1 ('MetaData "AssetUnion" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "MO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mortgage)) :+: (C1 ('MetaCons "LO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Loan)) :+: C1 ('MetaCons "IL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Installment)))) :+: ((C1 ('MetaCons "LS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lease)) :+: C1 ('MetaCons "FA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FixedAsset))) :+: (C1 ('MetaCons "RE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Receivable)) :+: C1 ('MetaCons "PF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectedCashflow))))) |
data MixedAsset Source #
Constructors
MixedPool (Map String [AssetUnion]) | |
DUMMY2 |
Instances
Generic MixedAsset Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show MixedAsset Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> MixedAsset -> ShowS # show :: MixedAsset -> String # showList :: [MixedAsset] -> ShowS # | |||||
Eq MixedAsset Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord MixedAsset Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: MixedAsset -> MixedAsset -> Ordering # (<) :: MixedAsset -> MixedAsset -> Bool # (<=) :: MixedAsset -> MixedAsset -> Bool # (>) :: MixedAsset -> MixedAsset -> Bool # (>=) :: MixedAsset -> MixedAsset -> Bool # max :: MixedAsset -> MixedAsset -> MixedAsset # min :: MixedAsset -> MixedAsset -> MixedAsset # | |||||
type Rep MixedAsset Source # | |||||
Defined in AssetClass.AssetBase type Rep MixedAsset = D1 ('MetaData "MixedAsset" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "MixedPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String [AssetUnion]))) :+: C1 ('MetaCons "DUMMY2" 'PrefixI 'False) (U1 :: Type -> Type)) |
data FixedAsset Source #
Constructors
FixedAsset OriginalInfo Balance RemainTerms | |
Dummy5 |
Instances
Asset FixedAsset Source # | |||||
Defined in AssetClass.FixedAsset Methods calcCashflow :: FixedAsset -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: FixedAsset -> Balance Source # getOriginBal :: FixedAsset -> Balance Source # getOriginRate :: FixedAsset -> IRate Source # getCurrentRate :: FixedAsset -> IRate Source # getOriginDate :: FixedAsset -> Date Source # getOriginInfo :: FixedAsset -> OriginalInfo Source # isDefaulted :: FixedAsset -> Bool Source # getPaymentDates :: FixedAsset -> Int -> [Date] Source # getRemainTerms :: FixedAsset -> Int Source # getRemainDates :: FixedAsset -> [Date] Source # getTotalTerms :: FixedAsset -> Int Source # getPastTerms :: FixedAsset -> Int Source # projCashflow :: FixedAsset -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: FixedAsset -> Int Source # splitWith :: FixedAsset -> [Rate] -> [FixedAsset] Source # updateOriginDate :: FixedAsset -> Date -> FixedAsset Source # resetToOrig :: FixedAsset -> FixedAsset Source # getLastInterestPaymentDate :: FixedAsset -> Maybe Date Source # calcAccruedInterest :: FixedAsset -> Date -> Balance Source # calcAlignDate :: FixedAsset -> Date -> Date Source # getObligor :: FixedAsset -> Maybe Obligor Source # getObligorTags :: FixedAsset -> Set String Source # getObligorId :: FixedAsset -> Maybe String Source # getObligorFields :: FixedAsset -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate FixedAsset Source # | |||||
Defined in AssetClass.AssetBase Methods isAdjustbleRate :: FixedAsset -> Bool Source # getIndex :: FixedAsset -> Maybe Index Source # getIndexes :: FixedAsset -> Maybe [Index] Source # getResetDates :: FixedAsset -> Dates Source # | |||||
FromJSON FixedAsset Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON FixedAsset Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: FixedAsset -> Value # toEncoding :: FixedAsset -> Encoding # toJSONList :: [FixedAsset] -> Value # toEncodingList :: [FixedAsset] -> Encoding # omitField :: FixedAsset -> Bool # | |||||
Generic FixedAsset Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show FixedAsset Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> FixedAsset -> ShowS # show :: FixedAsset -> String # showList :: [FixedAsset] -> ShowS # | |||||
Eq FixedAsset Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord FixedAsset Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: FixedAsset -> FixedAsset -> Ordering # (<) :: FixedAsset -> FixedAsset -> Bool # (<=) :: FixedAsset -> FixedAsset -> Bool # (>) :: FixedAsset -> FixedAsset -> Bool # (>=) :: FixedAsset -> FixedAsset -> Bool # max :: FixedAsset -> FixedAsset -> FixedAsset # min :: FixedAsset -> FixedAsset -> FixedAsset # | |||||
type Rep FixedAsset Source # | |||||
Defined in AssetClass.AssetBase type Rep FixedAsset = D1 ('MetaData "FixedAsset" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "FixedAsset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemainTerms))) :+: C1 ('MetaCons "Dummy5" 'PrefixI 'False) (U1 :: Type -> Type)) |
Constructors
DecliningBalance | DecliningBalance Method |
StraightLine | Straight Line Method |
Instances
FromJSON AmortRule Source # | |
Defined in AssetClass.AssetBase | |
ToJSON AmortRule Source # | |
Generic AmortRule Source # | |
Defined in AssetClass.AssetBase | |
Show AmortRule Source # | |
Eq AmortRule Source # | |
Ord AmortRule Source # | |
ToSchema AmortRule Source # | |
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy AmortRule -> Declare (Definitions Schema) NamedSchema # | |
type Rep AmortRule Source # | |
Constructors
FixedCapacity Balance | |
CapacityByTerm [(Int, Balance)] |
Instances
FromJSON Capacity Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Capacity Source # | |||||
Generic Capacity Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Capacity Source # | |||||
Eq Capacity Source # | |||||
Ord Capacity Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToSchema Capacity Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Capacity -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep Capacity Source # | |||||
Defined in AssetClass.AssetBase type Rep Capacity = D1 ('MetaData "Capacity" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "FixedCapacity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "CapacityByTerm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Balance)]))) |
data AssociateExp Source #
Constructors
ExpPerPeriod Balance | |
ExpPerUnit Balance |
Instances
FromJSON AssociateExp Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON AssociateExp Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: AssociateExp -> Value # toEncoding :: AssociateExp -> Encoding # toJSONList :: [AssociateExp] -> Value # toEncodingList :: [AssociateExp] -> Encoding # omitField :: AssociateExp -> Bool # | |||||
Generic AssociateExp Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show AssociateExp Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> AssociateExp -> ShowS # show :: AssociateExp -> String # showList :: [AssociateExp] -> ShowS # | |||||
Eq AssociateExp Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord AssociateExp Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: AssociateExp -> AssociateExp -> Ordering # (<) :: AssociateExp -> AssociateExp -> Bool # (<=) :: AssociateExp -> AssociateExp -> Bool # (>) :: AssociateExp -> AssociateExp -> Bool # (>=) :: AssociateExp -> AssociateExp -> Bool # max :: AssociateExp -> AssociateExp -> AssociateExp # min :: AssociateExp -> AssociateExp -> AssociateExp # | |||||
type Rep AssociateExp Source # | |||||
Defined in AssetClass.AssetBase type Rep AssociateExp = D1 ('MetaData "AssociateExp" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "ExpPerPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "ExpPerUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) |
data AssociateIncome Source #
Constructors
IncomePerPeriod Balance | |
IncomePerUnit Balance |
Instances
FromJSON AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase Methods parseJSON :: Value -> Parser AssociateIncome # parseJSONList :: Value -> Parser [AssociateIncome] # | |||||
ToJSON AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: AssociateIncome -> Value # toEncoding :: AssociateIncome -> Encoding # toJSONList :: [AssociateIncome] -> Value # toEncodingList :: [AssociateIncome] -> Encoding # omitField :: AssociateIncome -> Bool # | |||||
Generic AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase Associated Types
Methods from :: AssociateIncome -> Rep AssociateIncome x # to :: Rep AssociateIncome x -> AssociateIncome # | |||||
Show AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> AssociateIncome -> ShowS # show :: AssociateIncome -> String # showList :: [AssociateIncome] -> ShowS # | |||||
Eq AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase Methods (==) :: AssociateIncome -> AssociateIncome -> Bool # (/=) :: AssociateIncome -> AssociateIncome -> Bool # | |||||
Ord AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: AssociateIncome -> AssociateIncome -> Ordering # (<) :: AssociateIncome -> AssociateIncome -> Bool # (<=) :: AssociateIncome -> AssociateIncome -> Bool # (>) :: AssociateIncome -> AssociateIncome -> Bool # (>=) :: AssociateIncome -> AssociateIncome -> Bool # max :: AssociateIncome -> AssociateIncome -> AssociateIncome # min :: AssociateIncome -> AssociateIncome -> AssociateIncome # | |||||
type Rep AssociateIncome Source # | |||||
Defined in AssetClass.AssetBase type Rep AssociateIncome = D1 ('MetaData "AssociateIncome" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "IncomePerPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "IncomePerUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) |
data ReceivableFeeType Source #
Constructors
FixedFee Balance | a flat fee amount |
FixedRateFee Rate | a percentage fee against balance for once |
FactorFee Rate Int Direction | a percentage fee against balance for each period (N days) |
AdvanceFee Rate | annualized rate for discount fee based on advance amount |
CompoundFee [ReceivableFeeType] | compound fee |
Instances
FromJSON ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Methods parseJSON :: Value -> Parser ReceivableFeeType # parseJSONList :: Value -> Parser [ReceivableFeeType] # | |||||
ToJSON ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: ReceivableFeeType -> Value # toEncoding :: ReceivableFeeType -> Encoding # toJSONList :: [ReceivableFeeType] -> Value # toEncodingList :: [ReceivableFeeType] -> Encoding # omitField :: ReceivableFeeType -> Bool # | |||||
Generic ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Associated Types
Methods from :: ReceivableFeeType -> Rep ReceivableFeeType x # to :: Rep ReceivableFeeType x -> ReceivableFeeType # | |||||
Show ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> ReceivableFeeType -> ShowS # show :: ReceivableFeeType -> String # showList :: [ReceivableFeeType] -> ShowS # | |||||
Eq ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Methods (==) :: ReceivableFeeType -> ReceivableFeeType -> Bool # (/=) :: ReceivableFeeType -> ReceivableFeeType -> Bool # | |||||
Ord ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: ReceivableFeeType -> ReceivableFeeType -> Ordering # (<) :: ReceivableFeeType -> ReceivableFeeType -> Bool # (<=) :: ReceivableFeeType -> ReceivableFeeType -> Bool # (>) :: ReceivableFeeType -> ReceivableFeeType -> Bool # (>=) :: ReceivableFeeType -> ReceivableFeeType -> Bool # max :: ReceivableFeeType -> ReceivableFeeType -> ReceivableFeeType # min :: ReceivableFeeType -> ReceivableFeeType -> ReceivableFeeType # | |||||
ToSchema ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy ReceivableFeeType -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep ReceivableFeeType Source # | |||||
Defined in AssetClass.AssetBase type Rep ReceivableFeeType = D1 ('MetaData "ReceivableFeeType" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "FixedFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "FixedRateFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))) :+: (C1 ('MetaCons "FactorFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Direction))) :+: (C1 ('MetaCons "AdvanceFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "CompoundFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ReceivableFeeType]))))) |
data Receivable Source #
Constructors
Invoice OriginalInfo Status | |
DUMMY4 |
Instances
Asset Receivable Source # | |||||
Defined in AssetClass.Receivable Methods calcCashflow :: Receivable -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: Receivable -> Balance Source # getOriginBal :: Receivable -> Balance Source # getOriginRate :: Receivable -> IRate Source # getCurrentRate :: Receivable -> IRate Source # getOriginDate :: Receivable -> Date Source # getOriginInfo :: Receivable -> OriginalInfo Source # isDefaulted :: Receivable -> Bool Source # getPaymentDates :: Receivable -> Int -> [Date] Source # getRemainTerms :: Receivable -> Int Source # getRemainDates :: Receivable -> [Date] Source # getTotalTerms :: Receivable -> Int Source # getPastTerms :: Receivable -> Int Source # projCashflow :: Receivable -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: Receivable -> Int Source # splitWith :: Receivable -> [Rate] -> [Receivable] Source # updateOriginDate :: Receivable -> Date -> Receivable Source # resetToOrig :: Receivable -> Receivable Source # getLastInterestPaymentDate :: Receivable -> Maybe Date Source # calcAccruedInterest :: Receivable -> Date -> Balance Source # calcAlignDate :: Receivable -> Date -> Date Source # getObligor :: Receivable -> Maybe Obligor Source # getObligorTags :: Receivable -> Set String Source # getObligorId :: Receivable -> Maybe String Source # getObligorFields :: Receivable -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate Receivable Source # | |||||
Defined in AssetClass.AssetBase Methods isAdjustbleRate :: Receivable -> Bool Source # getIndex :: Receivable -> Maybe Index Source # getIndexes :: Receivable -> Maybe [Index] Source # getResetDates :: Receivable -> Dates Source # | |||||
FromJSON Receivable Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Receivable Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: Receivable -> Value # toEncoding :: Receivable -> Encoding # toJSONList :: [Receivable] -> Value # toEncodingList :: [Receivable] -> Encoding # omitField :: Receivable -> Bool # | |||||
Generic Receivable Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Receivable Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> Receivable -> ShowS # show :: Receivable -> String # showList :: [Receivable] -> ShowS # | |||||
Eq Receivable Source # | |||||
Defined in AssetClass.AssetBase | |||||
Ord Receivable Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: Receivable -> Receivable -> Ordering # (<) :: Receivable -> Receivable -> Bool # (<=) :: Receivable -> Receivable -> Bool # (>) :: Receivable -> Receivable -> Bool # (>=) :: Receivable -> Receivable -> Bool # max :: Receivable -> Receivable -> Receivable # min :: Receivable -> Receivable -> Receivable # | |||||
type Rep Receivable Source # | |||||
Defined in AssetClass.AssetBase type Rep Receivable = D1 ('MetaData "Receivable" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Invoice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OriginalInfo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)) :+: C1 ('MetaCons "DUMMY4" 'PrefixI 'False) (U1 :: Type -> Type)) |
data ProjectedCashflow Source #
Constructors
ProjectedFlowFixed CashFlowFrame DatePattern | |
ProjectedFlowMixFloater CashFlowFrame DatePattern FixRatePortion [FloatRatePortion] |
Instances
Asset ProjectedCashflow Source # | |||||
Defined in AssetClass.ProjectedCashFlow Methods calcCashflow :: ProjectedCashflow -> Date -> Maybe [RateAssumption] -> Either String CashFlowFrame Source # getCurrentBal :: ProjectedCashflow -> Balance Source # getOriginBal :: ProjectedCashflow -> Balance Source # getOriginRate :: ProjectedCashflow -> IRate Source # getCurrentRate :: ProjectedCashflow -> IRate Source # getOriginDate :: ProjectedCashflow -> Date Source # getOriginInfo :: ProjectedCashflow -> OriginalInfo Source # isDefaulted :: ProjectedCashflow -> Bool Source # getPaymentDates :: ProjectedCashflow -> Int -> [Date] Source # getRemainTerms :: ProjectedCashflow -> Int Source # getRemainDates :: ProjectedCashflow -> [Date] Source # getTotalTerms :: ProjectedCashflow -> Int Source # getPastTerms :: ProjectedCashflow -> Int Source # projCashflow :: ProjectedCashflow -> Date -> AssetPerf -> Maybe [RateAssumption] -> Either String (CashFlowFrame, Map CutoffFields Balance) Source # getBorrowerNum :: ProjectedCashflow -> Int Source # splitWith :: ProjectedCashflow -> [Rate] -> [ProjectedCashflow] Source # updateOriginDate :: ProjectedCashflow -> Date -> ProjectedCashflow Source # resetToOrig :: ProjectedCashflow -> ProjectedCashflow Source # getLastInterestPaymentDate :: ProjectedCashflow -> Maybe Date Source # calcAccruedInterest :: ProjectedCashflow -> Date -> Balance Source # calcAlignDate :: ProjectedCashflow -> Date -> Date Source # getObligor :: ProjectedCashflow -> Maybe Obligor Source # getObligorTags :: ProjectedCashflow -> Set String Source # getObligorId :: ProjectedCashflow -> Maybe String Source # getObligorFields :: ProjectedCashflow -> Maybe (Map String (Either String Double)) Source # | |||||
UseRate ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Methods isAdjustbleRate :: ProjectedCashflow -> Bool Source # getIndex :: ProjectedCashflow -> Maybe Index Source # getIndexes :: ProjectedCashflow -> Maybe [Index] Source # | |||||
FromJSON ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Methods parseJSON :: Value -> Parser ProjectedCashflow # parseJSONList :: Value -> Parser [ProjectedCashflow] # | |||||
ToJSON ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: ProjectedCashflow -> Value # toEncoding :: ProjectedCashflow -> Encoding # toJSONList :: [ProjectedCashflow] -> Value # toEncodingList :: [ProjectedCashflow] -> Encoding # omitField :: ProjectedCashflow -> Bool # | |||||
Generic ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Associated Types
Methods from :: ProjectedCashflow -> Rep ProjectedCashflow x # to :: Rep ProjectedCashflow x -> ProjectedCashflow # | |||||
Show ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> ProjectedCashflow -> ShowS # show :: ProjectedCashflow -> String # showList :: [ProjectedCashflow] -> ShowS # | |||||
Eq ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Methods (==) :: ProjectedCashflow -> ProjectedCashflow -> Bool # (/=) :: ProjectedCashflow -> ProjectedCashflow -> Bool # | |||||
Ord ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: ProjectedCashflow -> ProjectedCashflow -> Ordering # (<) :: ProjectedCashflow -> ProjectedCashflow -> Bool # (<=) :: ProjectedCashflow -> ProjectedCashflow -> Bool # (>) :: ProjectedCashflow -> ProjectedCashflow -> Bool # (>=) :: ProjectedCashflow -> ProjectedCashflow -> Bool # max :: ProjectedCashflow -> ProjectedCashflow -> ProjectedCashflow # min :: ProjectedCashflow -> ProjectedCashflow -> ProjectedCashflow # | |||||
type Rep ProjectedCashflow Source # | |||||
Defined in AssetClass.AssetBase |
Constructors
Obligor | |
Fields
|
Instances
FromJSON Obligor Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToJSON Obligor Source # | |||||
Generic Obligor Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show Obligor Source # | |||||
Eq Obligor Source # | |||||
Ord Obligor Source # | |||||
Defined in AssetClass.AssetBase | |||||
ToSchema Obligor Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Obligor -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep Obligor Source # | |||||
Defined in AssetClass.AssetBase type Rep Obligor = D1 ('MetaData "Obligor" "AssetClass.AssetBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "Obligor" 'PrefixI 'True) (S1 ('MetaSel ('Just "obligorId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "obligorTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "obligorFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String (Either String Double)))))) |
data LeaseRateCalc Source #
Constructors
ByDayRate DailyRate DatePattern | |
ByPeriodRental Balance Period |
Instances
FromJSON LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Methods parseJSON :: Value -> Parser LeaseRateCalc # parseJSONList :: Value -> Parser [LeaseRateCalc] # | |||||
ToJSON LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Methods toJSON :: LeaseRateCalc -> Value # toEncoding :: LeaseRateCalc -> Encoding # toJSONList :: [LeaseRateCalc] -> Value # toEncodingList :: [LeaseRateCalc] -> Encoding # omitField :: LeaseRateCalc -> Bool # | |||||
Generic LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Associated Types
| |||||
Show LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Methods showsPrec :: Int -> LeaseRateCalc -> ShowS # show :: LeaseRateCalc -> String # showList :: [LeaseRateCalc] -> ShowS # | |||||
Eq LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Methods (==) :: LeaseRateCalc -> LeaseRateCalc -> Bool # (/=) :: LeaseRateCalc -> LeaseRateCalc -> Bool # | |||||
Ord LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Methods compare :: LeaseRateCalc -> LeaseRateCalc -> Ordering # (<) :: LeaseRateCalc -> LeaseRateCalc -> Bool # (<=) :: LeaseRateCalc -> LeaseRateCalc -> Bool # (>) :: LeaseRateCalc -> LeaseRateCalc -> Bool # (>=) :: LeaseRateCalc -> LeaseRateCalc -> Bool # max :: LeaseRateCalc -> LeaseRateCalc -> LeaseRateCalc # min :: LeaseRateCalc -> LeaseRateCalc -> LeaseRateCalc # | |||||
ToSchema LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy LeaseRateCalc -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep LeaseRateCalc Source # | |||||
Defined in AssetClass.AssetBase |
calcAssetPrinInt :: AmortPlan -> Balance -> IRate -> Int -> Int -> (Balance, Int) -> (InterestAmount, PrincipalAmount) Source #
calcPmt :: Balance -> IRate -> Int -> Amount Source #
calculate period payment (Annuity/Level mortgage)
Orphan instances
ToSchema Decimal Source # | |
Methods declareNamedSchema :: Proxy Decimal -> Declare (Definitions Schema) NamedSchema # | |
ToSchema TsRow Source # | |
Methods declareNamedSchema :: Proxy TsRow -> Declare (Definitions Schema) NamedSchema # | |
ToSchema ARM Source # | |
Methods declareNamedSchema :: Proxy ARM -> Declare (Definitions Schema) NamedSchema # | |
ToSchema RateType Source # | |
Methods declareNamedSchema :: Proxy RateType -> Declare (Definitions Schema) NamedSchema # | |
ToSchema CutoffType Source # | |
Methods declareNamedSchema :: Proxy CutoffType -> Declare (Definitions Schema) NamedSchema # | |
ToSchema DatePattern Source # | |
Methods declareNamedSchema :: Proxy DatePattern -> Declare (Definitions Schema) NamedSchema # | |
ToSchema DayCount Source # | |
Methods declareNamedSchema :: Proxy DayCount -> Declare (Definitions Schema) NamedSchema # | |
ToSchema Direction Source # | |
Methods declareNamedSchema :: Proxy Direction -> Declare (Definitions Schema) NamedSchema # | |
ToSchema Index Source # | |
Methods declareNamedSchema :: Proxy Index -> Declare (Definitions Schema) NamedSchema # | |
ToSchema Period Source # | |
Methods declareNamedSchema :: Proxy Period -> Declare (Definitions Schema) NamedSchema # | |
ToSchema Ts Source # | |
Methods declareNamedSchema :: Proxy Ts -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (RoundingBy IRate) Source # | |
Methods declareNamedSchema :: Proxy (RoundingBy IRate) -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (TsPoint Balance) Source # | |
Methods declareNamedSchema :: Proxy (TsPoint Balance) -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (TsPoint IRate) Source # | |
Methods declareNamedSchema :: Proxy (TsPoint IRate) -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (TsPoint Rational) Source # | |
Methods declareNamedSchema :: Proxy (TsPoint Rational) -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (TsPoint Bool) Source # | |
Methods declareNamedSchema :: Proxy (TsPoint Bool) -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (TsPoint Int) Source # | |
Methods declareNamedSchema :: Proxy (TsPoint Int) -> Declare (Definitions Schema) NamedSchema # | |
ToSchema (Ratio Integer) Source # | |
Methods declareNamedSchema :: Proxy (Ratio Integer) -> Declare (Definitions Schema) NamedSchema # |