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

Deal.DealBase

Synopsis

Documentation

data TestDeal a Source #

Instances

Instances details
SPV (TestDeal a) Source # 
Instance details

Defined in Deal.DealBase

FromJSON a => FromJSON (TestDeal a) Source # 
Instance details

Defined in Deal.DealBase

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

Defined in Deal.DealBase

Generic (TestDeal a) Source # 
Instance details

Defined in Deal.DealBase

Associated Types

type Rep (TestDeal a) 
Instance details

Defined in Deal.DealBase

type Rep (TestDeal a)

Methods

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

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

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

Defined in Deal.DealBase

Methods

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

show :: TestDeal a -> String #

showList :: [TestDeal a] -> ShowS #

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

Defined in Deal.DealBase

Methods

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

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

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

Defined in Deal.DealBase

Methods

compare :: TestDeal a -> TestDeal a -> Ordering #

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

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

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

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

max :: TestDeal a -> TestDeal a -> TestDeal a #

min :: TestDeal a -> TestDeal a -> TestDeal a #

type Rep (TestDeal a) Source # 
Instance details

Defined in Deal.DealBase

type Rep (TestDeal a)

dealBonds :: Asset a => Lens' (TestDeal a) (Map BondName Bond) Source #

get & set bond group only

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

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 #

Instances

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

Defined in Deal.DealBase

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

Defined in Deal.DealBase

Generic (UnderlyingDeal a) Source # 
Instance details

Defined in Deal.DealBase

Associated Types

type Rep (UnderlyingDeal a) 
Instance details

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))))))
Show a => Show (UnderlyingDeal a) Source # 
Instance details

Defined in Deal.DealBase

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

Defined in Deal.DealBase

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

Defined in Deal.DealBase

type Rep (UnderlyingDeal a) Source # 
Instance details

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

viewDealAllBonds :: TestDeal a -> [Bond] Source #

flatten all bonds/bond groups in a map

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

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

viewDealBondsByNames :: Asset a => TestDeal a -> [BondName] -> [Bond] Source #

find bonds with first match

viewBondsInMap :: TestDeal a -> Map String Bond Source #

support bond group

data DealStatFields Source #

different types of deal stats

Instances

Instances details
FromJSON DealStatFields Source # 
Instance details

Defined in Types

FromJSONKey DealStatFields Source # 
Instance details

Defined in Deal.DealBase

ToJSON DealStatFields Source # 
Instance details

Defined in Types

ToJSONKey DealStatFields Source # 
Instance details

Defined in Deal.DealBase

Generic DealStatFields Source # 
Instance details

Defined in Types

Associated Types

type Rep DealStatFields 
Instance details

Defined in Types

type Rep DealStatFields = D1 ('MetaData "DealStatFields" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PoolCollectedPeriod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BondPaidPeriod" 'PrefixI 'False) (U1 :: Type -> Type))
Read DealStatFields Source # 
Instance details

Defined in Types

Show DealStatFields Source # 
Instance details

Defined in Types

Eq DealStatFields Source # 
Instance details

Defined in Types

Ord DealStatFields Source # 
Instance details

Defined in Types

type Rep DealStatFields Source # 
Instance details

Defined in Types

type Rep DealStatFields = D1 ('MetaData "DealStatFields" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PoolCollectedPeriod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BondPaidPeriod" 'PrefixI 'False) (U1 :: Type -> Type))

isPreClosing :: TestDeal a -> Bool Source #

list all bonds and bond groups in list

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 #

Orphan instances