Safe Haskell | None |
---|---|
Language | Haskell2010 |
Deal.DealBase
Contents
Synopsis
- data TestDeal a = TestDeal {
- name :: DealName
- status :: DealStatus
- dates :: DateDesp
- accounts :: Map AccountName Account
- fees :: Map FeeName Fee
- bonds :: Map BondName Bond
- pool :: PoolType a
- waterfall :: Map ActionWhen DistributionSeq
- collects :: [CollectionRule]
- stats :: (BalDealStatMap, RDealStatMap, BDealStatMap, IDealStatMap)
- liqProvider :: Maybe (Map String LiqFacility)
- rateSwap :: Maybe (Map String RateSwap)
- rateCap :: Maybe (Map String RateCap)
- currencySwap :: Maybe (Map String CurrencySwap)
- custom :: Maybe (Map String CustomDataType)
- triggers :: Maybe (Map DealCycle (Map String Trigger))
- ledgers :: Maybe (Map String Ledger)
- class SPV a where
- getBondsByName :: a -> Maybe [String] -> Map String Bond
- getActiveBonds :: a -> [String] -> [Bond]
- getBondBegBal :: a -> String -> Balance
- getBondStmtByName :: a -> Maybe [String] -> Map String (Maybe Statement)
- getFeeByName :: a -> Maybe [String] -> Map String Fee
- getAccountByName :: a -> Maybe [String] -> Map String Account
- isResec :: a -> Bool
- getNextBondPayDate :: a -> Date
- getOustandingBal :: a -> Balance
- dealBonds :: Asset a => Lens' (TestDeal a) (Map BondName Bond)
- dealFees :: Asset a => Lens' (TestDeal a) (Map FeeName Fee)
- dealAccounts :: Asset a => Lens' (TestDeal a) (Map AccountName Account)
- dealPool :: Asset a => Lens' (TestDeal a) (PoolType a)
- data PoolType a
- getIssuanceStats :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId (Map CutoffFields Balance)
- getAllAsset :: TestDeal a -> Maybe [PoolId] -> Map PoolId [a]
- getAllAssetList :: Asset a => TestDeal a -> [a]
- getAllCollectedFrame :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId CashFlowFrame
- getLatestCollectFrame :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId (Maybe TsRow)
- getAllCollectedTxns :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId [TsRow]
- getIssuanceStatsConsol :: Asset a => TestDeal a -> Maybe [PoolId] -> Map CutoffFields Balance
- getAllCollectedTxnsList :: Asset a => TestDeal a -> Maybe [PoolId] -> [TsRow]
- getPoolIds :: Asset a => TestDeal a -> [PoolId]
- getBondByName :: Asset a => TestDeal a -> Bool -> BondName -> Maybe Bond
- data UnderlyingDeal a = UnderlyingDeal {}
- uDealFutureTxn :: Asset a => Lens' (UnderlyingDeal a) [TsRow]
- viewDealAllBonds :: TestDeal a -> [Bond]
- data DateDesp
- = PreClosingDates CutoffDate ClosingDate (Maybe RevolvingDate) StatedDate (Date, PoolCollectionDates) (Date, DistributionDates)
- | CurrentDates (Date, Date) (Maybe Date) StatedDate (Date, PoolCollectionDates) (Date, DistributionDates)
- | GenericDates (Map DateType DatePattern)
- data ActionOnDate
- = EarnAccInt Date AccName
- | ChangeDealStatusTo Date DealStatus
- | AccrueFee Date FeeName
- | ResetLiqProvider Date String
- | ResetLiqProviderRate Date String
- | PoolCollection Date String
- | RunWaterfall Date String
- | DealClosed Date
- | FireTrigger Date DealCycle String
- | InspectDS Date [DealStats]
- | CalcIRSwap Date String
- | SettleIRSwap Date String
- | AccrueCapRate Date String
- | ResetBondRate Date String
- | StepUpBondRate Date String
- | ResetSrtRate Date String
- | ResetAccRate Date String
- | AccrueSrt Date String
- | MakeWhole Date Spread (Table Float Spread)
- | IssueBond Date (Maybe Pre) String AccName Bond (Maybe DealStats) (Maybe DealStats)
- | FundBond Date (Maybe Pre) String AccName Amount
- | RefiBondRate Date AccountName BondName InterestInfo
- | RefiBond Date AccountName Bond
- | BuildReport StartDate EndDate
- | StopRunFlag Date
- | StopRunTest Date [Pre]
- | HitStatedMaturity Date
- | TestCall Date
- sortActionOnDate :: ActionOnDate -> ActionOnDate -> Ordering
- dealBondGroups :: Asset a => Lens' (TestDeal a) (Map BondName Bond)
- viewDealBondsByNames :: Asset a => TestDeal a -> [BondName] -> [Bond]
- poolTypePool :: Asset a => Lens' (PoolType a) (Map PoolId (Pool a))
- viewBondsInMap :: TestDeal a -> Map String Bond
- bondGroupsBonds :: Lens' Bond (Map BondName Bond)
- increaseBondPaidPeriod :: TestDeal a -> TestDeal a
- increasePoolCollectedPeriod :: TestDeal a -> TestDeal a
- data DealStatFields
- getDealStatInt :: TestDeal a -> DealStatFields -> Maybe Int
- isPreClosing :: TestDeal a -> Bool
- populateDealDates :: DateDesp -> DealStatus -> Either String (Date, Date, Date, [ActionOnDate], [ActionOnDate], Date, [ActionOnDate])
- bondTraversal :: forall a f. Applicative f => (Bond -> f Bond) -> TestDeal a -> f (TestDeal a)
- findBondByNames :: Map String Bond -> [BondName] -> Either String [Bond]
- updateBondInMap :: BondName -> (Bond -> Bond) -> Map BondName Bond -> Map BondName Bond
- _MultiPool :: forall a p f. (Choice p, Applicative f) => p (Map PoolId (Pool a)) (f (Map PoolId (Pool a))) -> p (PoolType a) (f (PoolType a))
- _ResecDeal :: forall a p f. (Choice p, Applicative f) => p (Map PoolId (UnderlyingDeal a)) (f (Map PoolId (UnderlyingDeal a))) -> p (PoolType a) (f (PoolType a))
- uDealFutureCf :: Asset a => Lens' (UnderlyingDeal a) CashFlowFrame
- uDealFutureScheduleCf :: Asset a => Lens' (UnderlyingDeal a) CashFlowFrame
Documentation
Constructors
TestDeal | |
Fields
|
Instances
SPV (TestDeal a) Source # | |
Defined in Deal.DealBase Methods getBondsByName :: TestDeal a -> Maybe [String] -> Map String Bond Source # getActiveBonds :: TestDeal a -> [String] -> [Bond] Source # getBondBegBal :: TestDeal a -> String -> Balance Source # getBondStmtByName :: TestDeal a -> Maybe [String] -> Map String (Maybe Statement) Source # getFeeByName :: TestDeal a -> Maybe [String] -> Map String Fee Source # getAccountByName :: TestDeal a -> Maybe [String] -> Map String Account Source # isResec :: TestDeal a -> Bool Source # getNextBondPayDate :: TestDeal a -> Date Source # getOustandingBal :: TestDeal a -> Balance Source # | |
FromJSON a => FromJSON (TestDeal a) Source # | |
Defined in Deal.DealBase | |
ToJSON a => ToJSON (TestDeal a) Source # | |
Generic (TestDeal a) Source # | |
Show a => Show (TestDeal a) Source # | |
Eq a => Eq (TestDeal a) Source # | |
Ord a => Ord (TestDeal a) Source # | |
type Rep (TestDeal a) Source # | |
Defined in Deal.DealBase |
Methods
getBondsByName :: a -> Maybe [String] -> Map String Bond Source #
getActiveBonds :: a -> [String] -> [Bond] Source #
getBondBegBal :: a -> String -> Balance Source #
getBondStmtByName :: a -> Maybe [String] -> Map String (Maybe Statement) Source #
getFeeByName :: a -> Maybe [String] -> Map String Fee Source #
getAccountByName :: a -> Maybe [String] -> Map String Account Source #
getNextBondPayDate :: a -> Date Source #
getOustandingBal :: a -> Balance Source #
Instances
SPV (TestDeal a) Source # | |
Defined in Deal.DealBase Methods getBondsByName :: TestDeal a -> Maybe [String] -> Map String Bond Source # getActiveBonds :: TestDeal a -> [String] -> [Bond] Source # getBondBegBal :: TestDeal a -> String -> Balance Source # getBondStmtByName :: TestDeal a -> Maybe [String] -> Map String (Maybe Statement) Source # getFeeByName :: TestDeal a -> Maybe [String] -> Map String Fee Source # getAccountByName :: TestDeal a -> Maybe [String] -> Map String Account Source # isResec :: TestDeal a -> Bool Source # getNextBondPayDate :: TestDeal a -> Date Source # getOustandingBal :: TestDeal a -> Balance Source # |
dealAccounts :: Asset a => Lens' (TestDeal a) (Map AccountName Account) Source #
Instances
getIssuanceStats :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId (Map CutoffFields Balance) Source #
getAllAssetList :: Asset a => TestDeal a -> [a] Source #
getAllCollectedFrame :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId CashFlowFrame Source #
getLatestCollectFrame :: Asset a => TestDeal a -> Maybe [PoolId] -> Map PoolId (Maybe TsRow) Source #
getIssuanceStatsConsol :: Asset a => TestDeal a -> Maybe [PoolId] -> Map CutoffFields Balance Source #
getPoolIds :: Asset a => TestDeal a -> [PoolId] Source #
to handle with bond group, with flag to good deep if it is a bond group
getBondByName :: Asset a => TestDeal a -> Bool -> BondName -> Maybe Bond Source #
get issuance pool stat from pool map
data UnderlyingDeal a Source #
Constructors
UnderlyingDeal | |
Fields
|
Instances
FromJSON a => FromJSON (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase Methods parseJSON :: Value -> Parser (UnderlyingDeal a) # parseJSONList :: Value -> Parser [UnderlyingDeal a] # omittedField :: Maybe (UnderlyingDeal a) # | |||||
ToJSON a => ToJSON (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase Methods toJSON :: UnderlyingDeal a -> Value # toEncoding :: UnderlyingDeal a -> Encoding # toJSONList :: [UnderlyingDeal a] -> Value # toEncodingList :: [UnderlyingDeal a] -> Encoding # omitField :: UnderlyingDeal a -> Bool # | |||||
Generic (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase Associated Types
Methods from :: UnderlyingDeal a -> Rep (UnderlyingDeal a) x # to :: Rep (UnderlyingDeal a) x -> UnderlyingDeal a # | |||||
Show a => Show (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase Methods showsPrec :: Int -> UnderlyingDeal a -> ShowS # show :: UnderlyingDeal a -> String # showList :: [UnderlyingDeal a] -> ShowS # | |||||
Eq a => Eq (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase Methods (==) :: UnderlyingDeal a -> UnderlyingDeal a -> Bool # (/=) :: UnderlyingDeal a -> UnderlyingDeal a -> Bool # | |||||
Ord a => Ord (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase Methods compare :: UnderlyingDeal a -> UnderlyingDeal a -> Ordering # (<) :: UnderlyingDeal a -> UnderlyingDeal a -> Bool # (<=) :: UnderlyingDeal a -> UnderlyingDeal a -> Bool # (>) :: UnderlyingDeal a -> UnderlyingDeal a -> Bool # (>=) :: UnderlyingDeal a -> UnderlyingDeal a -> Bool # max :: UnderlyingDeal a -> UnderlyingDeal a -> UnderlyingDeal a # min :: UnderlyingDeal a -> UnderlyingDeal a -> UnderlyingDeal a # | |||||
type Rep (UnderlyingDeal a) Source # | |||||
Defined in Deal.DealBase type Rep (UnderlyingDeal a) = D1 ('MetaData "UnderlyingDeal" "Deal.DealBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "UnderlyingDeal" 'PrefixI 'True) ((S1 ('MetaSel ('Just "deal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TestDeal a)) :*: S1 ('MetaSel ('Just "futureCf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CashFlowFrame)) :*: (S1 ('MetaSel ('Just "futureScheduleCf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CashFlowFrame) :*: S1 ('MetaSel ('Just "issuanceStat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map CutoffFields Balance)))))) |
uDealFutureTxn :: Asset a => Lens' (UnderlyingDeal a) [TsRow] Source #
viewDealAllBonds :: TestDeal a -> [Bond] Source #
flatten all bonds/bond groups in a map
Constructors
PreClosingDates CutoffDate ClosingDate (Maybe RevolvingDate) StatedDate (Date, PoolCollectionDates) (Date, DistributionDates) | |
CurrentDates (Date, Date) (Maybe Date) StatedDate (Date, PoolCollectionDates) (Date, DistributionDates) | |
GenericDates (Map DateType DatePattern) |
Instances
data ActionOnDate Source #
Constructors
EarnAccInt Date AccName | sweep bank account interest |
ChangeDealStatusTo Date DealStatus | change deal status |
AccrueFee Date FeeName | accure fee |
ResetLiqProvider Date String | reset credit for liquidity provider |
ResetLiqProviderRate Date String | accure interest/premium amount for liquidity provider |
PoolCollection Date String | collect pool cashflow and deposit to accounts |
RunWaterfall Date String | execute waterfall on distribution date |
DealClosed Date | actions to perform at the deal closing day, and enter a new deal status |
FireTrigger Date DealCycle String | fire a trigger |
InspectDS Date [DealStats] | inspect formulas |
CalcIRSwap Date String | calc interest rate swap dates |
SettleIRSwap Date String | settle interest rate swap dates |
AccrueCapRate Date String | reset interest rate cap dates |
ResetBondRate Date String | reset bond interest rate per bond's interest rate info |
StepUpBondRate Date String | reset bond interest rate per bond's interest rate info |
ResetSrtRate Date String | |
ResetAccRate Date String | |
AccrueSrt Date String | |
MakeWhole Date Spread (Table Float Spread) | |
IssueBond Date (Maybe Pre) String AccName Bond (Maybe DealStats) (Maybe DealStats) | |
FundBond Date (Maybe Pre) String AccName Amount | |
RefiBondRate Date AccountName BondName InterestInfo | |
RefiBond Date AccountName Bond | |
BuildReport StartDate EndDate | build cashflow report between dates and balance report at end date |
StopRunFlag Date | stop the run with a message |
StopRunTest Date [Pre] | stop the run with a condition |
HitStatedMaturity Date | hit the stated maturity date |
TestCall Date | test call dates |
Instances
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 # | |||||
FromJSON ActionOnDate Source # | |||||
Defined in Deal.DealBase | |||||
ToJSON ActionOnDate Source # | |||||
Defined in Deal.DealBase Methods toJSON :: ActionOnDate -> Value # toEncoding :: ActionOnDate -> Encoding # toJSONList :: [ActionOnDate] -> Value # toEncodingList :: [ActionOnDate] -> Encoding # omitField :: ActionOnDate -> Bool # | |||||
Generic ActionOnDate Source # | |||||
Defined in Deal.DealBase Associated Types
| |||||
Read ActionOnDate Source # | |||||
Defined in Deal.DealBase Methods readsPrec :: Int -> ReadS ActionOnDate # readList :: ReadS [ActionOnDate] # | |||||
Show ActionOnDate Source # | |||||
Defined in Deal.DealBase Methods showsPrec :: Int -> ActionOnDate -> ShowS # show :: ActionOnDate -> String # showList :: [ActionOnDate] -> ShowS # | |||||
Eq ActionOnDate Source # | |||||
Defined in Deal.DealBase | |||||
Ord ActionOnDate Source # | |||||
Defined in Deal.DealBase Methods compare :: ActionOnDate -> ActionOnDate -> Ordering # (<) :: ActionOnDate -> ActionOnDate -> Bool # (<=) :: ActionOnDate -> ActionOnDate -> Bool # (>) :: ActionOnDate -> ActionOnDate -> Bool # (>=) :: ActionOnDate -> ActionOnDate -> Bool # max :: ActionOnDate -> ActionOnDate -> ActionOnDate # min :: ActionOnDate -> ActionOnDate -> ActionOnDate # | |||||
type Rep ActionOnDate Source # | |||||
Defined in Deal.DealBase type Rep ActionOnDate = D1 ('MetaData "ActionOnDate" "Deal.DealBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "EarnAccInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName)) :+: (C1 ('MetaCons "ChangeDealStatusTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :+: C1 ('MetaCons "AccrueFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)))) :+: ((C1 ('MetaCons "ResetLiqProvider" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ResetLiqProviderRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "PoolCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "RunWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) :+: ((C1 ('MetaCons "DealClosed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "FireTrigger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealCycle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "InspectDS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))) :+: ((C1 ('MetaCons "CalcIRSwap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "SettleIRSwap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "AccrueCapRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ResetBondRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))) :+: (((C1 ('MetaCons "StepUpBondRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "ResetSrtRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ResetAccRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "AccrueSrt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "MakeWhole" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Spread) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Table Float Spread))))) :+: (C1 ('MetaCons "IssueBond" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Pre)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bond)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DealStats)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DealStats))))) :+: C1 ('MetaCons "FundBond" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Pre))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))))))) :+: ((C1 ('MetaCons "RefiBondRate" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InterestInfo))) :+: (C1 ('MetaCons "RefiBond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bond))) :+: C1 ('MetaCons "BuildReport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartDate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndDate)))) :+: ((C1 ('MetaCons "StopRunFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "StopRunTest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre]))) :+: (C1 ('MetaCons "HitStatedMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "TestCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))))))) |
sortActionOnDate :: ActionOnDate -> ActionOnDate -> Ordering Source #
viewDealBondsByNames :: Asset a => TestDeal a -> [BondName] -> [Bond] Source #
find bonds with first match
increaseBondPaidPeriod :: TestDeal a -> TestDeal a Source #
increasePoolCollectedPeriod :: TestDeal a -> TestDeal a Source #
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 # | |||||
getDealStatInt :: TestDeal a -> DealStatFields -> Maybe Int Source #
isPreClosing :: TestDeal a -> Bool Source #
list all bonds and bond groups in list
populateDealDates :: DateDesp -> DealStatus -> Either String (Date, Date, Date, [ActionOnDate], [ActionOnDate], Date, [ActionOnDate]) Source #
bondTraversal :: forall a f. Applicative f => (Bond -> f Bond) -> TestDeal a -> f (TestDeal a) Source #
findBondByNames :: Map String Bond -> [BondName] -> Either String [Bond] Source #
not support bond group
_MultiPool :: forall a p f. (Choice p, Applicative f) => p (Map PoolId (Pool a)) (f (Map PoolId (Pool a))) -> p (PoolType a) (f (PoolType a)) Source #
_ResecDeal :: forall a p f. (Choice p, Applicative f) => p (Map PoolId (UnderlyingDeal a)) (f (Map PoolId (UnderlyingDeal a))) -> p (PoolType a) (f (PoolType a)) Source #
uDealFutureCf :: Asset a => Lens' (UnderlyingDeal a) CashFlowFrame Source #
uDealFutureScheduleCf :: Asset a => Lens' (UnderlyingDeal a) CashFlowFrame Source #