Hastructure-0.50.0: Cashflow modeling library for structured finance
Safe HaskellNone
LanguageHaskell2010

Deal

Synopsis

Documentation

runPool :: Asset a => Pool a -> Maybe ApplyAssumptionType -> Maybe [RateAssumption] -> Either String [(CashFlowFrame, Map CutoffFields Balance)] Source #

run a pool of assets ,use asOfDate of Pool to cutoff cashflow yields from assets with assumptions supplied

patch issuance balance for PreClosing Deal

data ExpectReturn Source #

Constructors

DealLogs 
AssetLevelFlow 

Instances

Instances details
FromJSON ExpectReturn Source # 
Instance details

Defined in Deal

ToJSON ExpectReturn Source # 
Instance details

Defined in Deal

Generic ExpectReturn Source # 
Instance details

Defined in Deal

Associated Types

type Rep ExpectReturn 
Instance details

Defined in Deal

type Rep ExpectReturn = D1 ('MetaData "ExpectReturn" "Deal" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "DealLogs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AssetLevelFlow" 'PrefixI 'False) (U1 :: Type -> Type))
Show ExpectReturn Source # 
Instance details

Defined in Deal

Eq ExpectReturn Source # 
Instance details

Defined in Deal

Ord ExpectReturn Source # 
Instance details

Defined in Deal

type Rep ExpectReturn Source # 
Instance details

Defined in Deal

type Rep ExpectReturn = D1 ('MetaData "ExpectReturn" "Deal" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "DealLogs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AssetLevelFlow" 'PrefixI 'False) (U1 :: Type -> Type))

accrueRC :: Asset a => TestDeal a -> Date -> [RateAssumption] -> RateCap -> Either String RateCap Source #

test if a clean up call should be fired

calcTargetAmount :: Asset a => TestDeal a -> Date -> Account -> Either String Balance Source #

calcuate target balance for a reserve account, 0 for a non-reserve account

updateLiqProvider :: Asset a => TestDeal a -> Date -> LiqFacility -> LiqFacility Source #

TODO : to be replace from L.accrueInt Not possible to use L.accrueInt, since the interest may use formula to query on deal's stats

data PoolType a Source #

Instances

Instances details
FromJSON a => FromJSON (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

ToJSON a => ToJSON (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

Generic (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

Associated Types

type Rep (PoolType a) 
Instance details

Defined in Deal.DealBase

type Rep (PoolType a) = D1 ('MetaData "PoolType" "Deal.DealBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "MultiPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PoolId (Pool a)))) :+: C1 ('MetaCons "ResecDeal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PoolId (UnderlyingDeal a)))))

Methods

from :: PoolType a -> Rep (PoolType a) x #

to :: Rep (PoolType a) x -> PoolType a #

Show a => Show (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

Methods

showsPrec :: Int -> PoolType a -> ShowS #

show :: PoolType a -> String #

showList :: [PoolType a] -> ShowS #

Eq a => Eq (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

Methods

(==) :: PoolType a -> PoolType a -> Bool #

(/=) :: PoolType a -> PoolType a -> Bool #

Ord a => Ord (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

Methods

compare :: PoolType a -> PoolType a -> Ordering #

(<) :: PoolType a -> PoolType a -> Bool #

(<=) :: PoolType a -> PoolType a -> Bool #

(>) :: PoolType a -> PoolType a -> Bool #

(>=) :: PoolType a -> PoolType a -> Bool #

max :: PoolType a -> PoolType a -> PoolType a #

min :: PoolType a -> PoolType a -> PoolType a #

type Rep (PoolType a) Source # 
Instance details

Defined in Deal.DealBase

type Rep (PoolType a) = D1 ('MetaData "PoolType" "Deal.DealBase" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "MultiPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PoolId (Pool a)))) :+: C1 ('MetaCons "ResecDeal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PoolId (UnderlyingDeal a)))))

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

Instances details
TimeSeries ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

FromJSON ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

ToJSON ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

Generic ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

Associated Types

type Rep ActionOnDate 
Instance details

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)))))))
Read ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

Show ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

Eq ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

Ord ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

type Rep ActionOnDate Source # 
Instance details

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)))))))

data DateDesp Source #

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

Instances details
DealDates DateDesp Source # 
Instance details

Defined in Deal.DealDate

FromJSON DateDesp Source # 
Instance details

Defined in Deal.DealBase

ToJSON DateDesp Source # 
Instance details

Defined in Deal.DealBase

Generic DateDesp Source # 
Instance details

Defined in Deal.DealBase

Associated Types

type Rep DateDesp 
Instance details

Defined in Deal.DealBase

Methods

from :: DateDesp -> Rep DateDesp x #

to :: Rep DateDesp x -> DateDesp #

Show DateDesp Source # 
Instance details

Defined in Deal.DealBase

Eq DateDesp Source # 
Instance details

Defined in Deal.DealBase

Ord DateDesp Source # 
Instance details

Defined in Deal.DealBase

type Rep DateDesp Source # 
Instance details

Defined in Deal.DealBase

changeDealStatus :: Asset a => (Date, String) -> DealStatus -> TestDeal a -> (Maybe ResultComponent, TestDeal a) Source #

no status change for deal already ended