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

Types

Synopsis

Documentation

data DayCount Source #

Constructors

DC_30E_360

ISMA European 30S/360 Special German Eurobond Basis

DC_30Ep_360

30E+/360

DC_ACT_360

Actual/360 , French

DC_ACT_365 
DC_ACT_365A

Actual/365 Actual

DC_ACT_365L

Actual/365 Leap Year

DC_NL_365

Actual/365 No leap year

DC_ACT_365F

Actual /365 Fixed, English

DC_ACT_ACT

Actual/Actual ISDA

DC_30_360_ISDA

IDSA

DC_30_360_German

Gernman

DC_30_360_US

30/360 US Municipal , Bond basis

Instances

Instances details
FromJSON DayCount Source # 
Instance details

Defined in Types

ToJSON DayCount Source # 
Instance details

Defined in Types

Generic DayCount Source # 
Instance details

Defined in Types

Associated Types

type Rep DayCount 
Instance details

Defined in Types

type Rep DayCount = D1 ('MetaData "DayCount" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "DC_30E_360" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_30Ep_360" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_360" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DC_ACT_365" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_ACT_365A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_365L" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DC_NL_365" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_ACT_365F" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_ACT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DC_30_360_ISDA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_30_360_German" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_30_360_US" 'PrefixI 'False) (U1 :: Type -> Type)))))

Methods

from :: DayCount -> Rep DayCount x #

to :: Rep DayCount x -> DayCount #

Read DayCount Source # 
Instance details

Defined in Types

Show DayCount Source # 
Instance details

Defined in Types

Eq DayCount Source # 
Instance details

Defined in Types

Ord DayCount Source # 
Instance details

Defined in Types

ToSchema DayCount Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep DayCount Source # 
Instance details

Defined in Types

type Rep DayCount = D1 ('MetaData "DayCount" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "DC_30E_360" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_30Ep_360" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_360" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DC_ACT_365" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_ACT_365A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_365L" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DC_NL_365" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_ACT_365F" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_ACT_ACT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DC_30_360_ISDA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DC_30_360_German" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DC_30_360_US" 'PrefixI 'False) (U1 :: Type -> Type)))))

data DateType Source #

Constructors

ClosingDate

deal closing day

CutoffDate

after which, the pool cashflow was aggregated to SPV

FirstPayDate

first payment day for bond/waterfall to run with

NextPayDate 
NextCollectDate 
FirstCollectDate

first collection day for pool

LastCollectDate

last collection day for pool

LastPayDate

last payment day for bond/waterfall

StatedMaturityDate

sated maturity date, all cashflow projection/deal action stops by

DistributionDates

distribution date for waterfall

CollectionDates

collection date for pool

CustomExeDates String

custom execution date

Instances

Instances details
FromJSON DateType Source # 
Instance details

Defined in Types

FromJSONKey DateType Source # 
Instance details

Defined in Types

ToJSON DateType Source # 
Instance details

Defined in Types

ToJSONKey DateType Source # 
Instance details

Defined in Types

Generic DateType Source # 
Instance details

Defined in Types

Associated Types

type Rep DateType 
Instance details

Defined in Types

type Rep DateType = D1 ('MetaData "DateType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "ClosingDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CutoffDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FirstPayDate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NextPayDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NextCollectDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FirstCollectDate" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LastCollectDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LastPayDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StatedMaturityDate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DistributionDates" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectionDates" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CustomExeDates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

Methods

from :: DateType -> Rep DateType x #

to :: Rep DateType x -> DateType #

Read DateType Source # 
Instance details

Defined in Types

Show DateType Source # 
Instance details

Defined in Types

Eq DateType Source # 
Instance details

Defined in Types

Ord DateType Source # 
Instance details

Defined in Types

type Rep DateType Source # 
Instance details

Defined in Types

type Rep DateType = D1 ('MetaData "DateType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "ClosingDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CutoffDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FirstPayDate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NextPayDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NextCollectDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FirstCollectDate" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LastCollectDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LastPayDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StatedMaturityDate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DistributionDates" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectionDates" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CustomExeDates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

data DatePattern Source #

Instances

Instances details
FromJSON DatePattern Source # 
Instance details

Defined in Types

ToJSON DatePattern Source # 
Instance details

Defined in Types

Generic DatePattern Source # 
Instance details

Defined in Types

Associated Types

type Rep DatePattern 
Instance details

Defined in Types

type Rep DatePattern = D1 ('MetaData "DatePattern" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "MonthEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuarterEnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "YearEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonthFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuarterFirst" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MidYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "YearFirst" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonthDayOfYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "DayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "SemiAnnual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int))))))) :+: (((C1 ('MetaCons "CustomDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Date])) :+: C1 ('MetaCons "SingletonDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))) :+: (C1 ('MetaCons "DaysInYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Int)])) :+: (C1 ('MetaCons "EveryNMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Weekday" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "AllDatePattern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DatePattern])) :+: (C1 ('MetaCons "StartsExclusive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern)) :+: C1 ('MetaCons "StartsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CutoffType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))))) :+: (C1 ('MetaCons "EndsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CutoffType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))) :+: (C1 ('MetaCons "Exclude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DatePattern])) :+: C1 ('MetaCons "OffsetBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))))
Read DatePattern Source # 
Instance details

Defined in Types

Show DatePattern Source #

DayOfWeek Int -- T.DayOfWeek

Instance details

Defined in Types

Eq DatePattern Source # 
Instance details

Defined in Types

Ord DatePattern Source # 
Instance details

Defined in Types

ToSchema DatePattern Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep DatePattern Source # 
Instance details

Defined in Types

type Rep DatePattern = D1 ('MetaData "DatePattern" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "MonthEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuarterEnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "YearEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonthFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuarterFirst" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MidYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "YearFirst" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonthDayOfYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "DayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "SemiAnnual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int))))))) :+: (((C1 ('MetaCons "CustomDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Date])) :+: C1 ('MetaCons "SingletonDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))) :+: (C1 ('MetaCons "DaysInYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Int)])) :+: (C1 ('MetaCons "EveryNMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Weekday" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "AllDatePattern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DatePattern])) :+: (C1 ('MetaCons "StartsExclusive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern)) :+: C1 ('MetaCons "StartsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CutoffType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))))) :+: (C1 ('MetaCons "EndsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CutoffType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern))) :+: (C1 ('MetaCons "Exclude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DatePattern])) :+: C1 ('MetaCons "OffsetBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))))

data Ts Source #

Instances

Instances details
FromJSON Ts Source # 
Instance details

Defined in Types

ToJSON Ts Source # 
Instance details

Defined in Types

Generic Ts Source # 
Instance details

Defined in Types

Associated Types

type Rep Ts 
Instance details

Defined in Types

type Rep Ts = D1 ('MetaData "Ts" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "FloatCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: C1 ('MetaCons "BoolCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Bool]))) :+: (C1 ('MetaCons "BalanceCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Balance])) :+: (C1 ('MetaCons "LeftBalanceCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Balance])) :+: C1 ('MetaCons "RatioCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational]))))) :+: ((C1 ('MetaCons "ThresholdCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: (C1 ('MetaCons "IRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint IRate])) :+: C1 ('MetaCons "FactorCurveClosed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: (C1 ('MetaCons "PricingCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: (C1 ('MetaCons "PeriodCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Int])) :+: C1 ('MetaCons "IntCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Int]))))))

Methods

from :: Ts -> Rep Ts x #

to :: Rep Ts x -> Ts #

Read Ts Source # 
Instance details

Defined in Types

Show Ts Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Ts -> ShowS #

show :: Ts -> String #

showList :: [Ts] -> ShowS #

Eq Ts Source # 
Instance details

Defined in Types

Methods

(==) :: Ts -> Ts -> Bool #

(/=) :: Ts -> Ts -> Bool #

Ord Ts Source # 
Instance details

Defined in Types

Methods

compare :: Ts -> Ts -> Ordering #

(<) :: Ts -> Ts -> Bool #

(<=) :: Ts -> Ts -> Bool #

(>) :: Ts -> Ts -> Bool #

(>=) :: Ts -> Ts -> Bool #

max :: Ts -> Ts -> Ts #

min :: Ts -> Ts -> Ts #

ToSchema Ts Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep Ts Source # 
Instance details

Defined in Types

type Rep Ts = D1 ('MetaData "Ts" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "FloatCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: C1 ('MetaCons "BoolCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Bool]))) :+: (C1 ('MetaCons "BalanceCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Balance])) :+: (C1 ('MetaCons "LeftBalanceCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Balance])) :+: C1 ('MetaCons "RatioCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational]))))) :+: ((C1 ('MetaCons "ThresholdCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: (C1 ('MetaCons "IRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint IRate])) :+: C1 ('MetaCons "FactorCurveClosed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: (C1 ('MetaCons "PricingCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Rational])) :+: (C1 ('MetaCons "PeriodCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Int])) :+: C1 ('MetaCons "IntCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Int]))))))

data TsPoint a Source #

Constructors

TsPoint Date a 

Instances

Instances details
TimeSeries (TsPoint a) Source # 
Instance details

Defined in Types

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

Defined in Types

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

Defined in Types

Generic (TsPoint a) Source # 
Instance details

Defined in Types

Associated Types

type Rep (TsPoint a) 
Instance details

Defined in Types

type Rep (TsPoint a) = D1 ('MetaData "TsPoint" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "TsPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

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

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

Read a => Read (TsPoint a) Source # 
Instance details

Defined in Types

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

Defined in Types

Methods

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

show :: TsPoint a -> String #

showList :: [TsPoint a] -> ShowS #

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

Defined in Types

Methods

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

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

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

Defined in Types

Methods

compare :: TsPoint a -> TsPoint a -> Ordering #

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

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

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

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

max :: TsPoint a -> TsPoint a -> TsPoint a #

min :: TsPoint a -> TsPoint a -> TsPoint a #

ToSchema (TsPoint Balance) Source # 
Instance details

Defined in AssetClass.AssetBase

ToSchema (TsPoint IRate) Source # 
Instance details

Defined in AssetClass.AssetBase

ToSchema (TsPoint Rational) Source # 
Instance details

Defined in AssetClass.AssetBase

ToSchema (TsPoint Bool) Source # 
Instance details

Defined in AssetClass.AssetBase

ToSchema (TsPoint Int) Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep (TsPoint a) Source # 
Instance details

Defined in Types

type Rep (TsPoint a) = D1 ('MetaData "TsPoint" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "TsPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data PoolSource Source #

Constructors

CollectedInterest

interest

CollectedPrincipal

schdule principal

CollectedRecoveries

recoveries

CollectedPrepayment

prepayment

CollectedPrepaymentPenalty

prepayment pentalty

CollectedRental

rental from pool

CollectedFeePaid

fee from pool

CollectedCash

cash from pool

NewDefaults

new defaults in balance

NewLosses

new losses in balance

NewDelinquencies

new delinquencies in balance

CurBalance

performing balance

CurBegBalance

performing balance at the beginning of the period

Instances

Instances details
FromJSON PoolSource Source # 
Instance details

Defined in Types

ToJSON PoolSource Source # 
Instance details

Defined in Types

Generic PoolSource Source # 
Instance details

Defined in Types

Associated Types

type Rep PoolSource 
Instance details

Defined in Types

type Rep PoolSource = D1 ('MetaData "PoolSource" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "CollectedInterest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedPrincipal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectedRecoveries" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CollectedPrepayment" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedPrepaymentPenalty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectedRental" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CollectedFeePaid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedCash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewDefaults" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NewLosses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewDelinquencies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CurBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurBegBalance" 'PrefixI 'False) (U1 :: Type -> Type)))))
Read PoolSource Source # 
Instance details

Defined in Types

Show PoolSource Source # 
Instance details

Defined in Types

Eq PoolSource Source # 
Instance details

Defined in Types

Ord PoolSource Source # 
Instance details

Defined in Types

type Rep PoolSource Source # 
Instance details

Defined in Types

type Rep PoolSource = D1 ('MetaData "PoolSource" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "CollectedInterest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedPrincipal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectedRecoveries" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CollectedPrepayment" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedPrepaymentPenalty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectedRental" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CollectedFeePaid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CollectedCash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewDefaults" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NewLosses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewDelinquencies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CurBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurBegBalance" 'PrefixI 'False) (U1 :: Type -> Type)))))

data PerPoint a Source #

Constructors

PerPoint Int a 

Instances

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

Defined in Types

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

Defined in Types

Generic (PerPoint a) Source # 
Instance details

Defined in Types

Associated Types

type Rep (PerPoint a) 
Instance details

Defined in Types

type Rep (PerPoint a) = D1 ('MetaData "PerPoint" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PerPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

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

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

Read a => Read (PerPoint a) Source # 
Instance details

Defined in Types

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

Defined in Types

Methods

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

show :: PerPoint a -> String #

showList :: [PerPoint a] -> ShowS #

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

Defined in Types

Methods

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

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

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

Defined in Types

Methods

compare :: PerPoint a -> PerPoint a -> Ordering #

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

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

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

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

max :: PerPoint a -> PerPoint a -> PerPoint a #

min :: PerPoint a -> PerPoint a -> PerPoint a #

type Rep (PerPoint a) Source # 
Instance details

Defined in Types

type Rep (PerPoint a) = D1 ('MetaData "PerPoint" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "PerPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data PerCurve a Source #

Constructors

CurrentVal [PerPoint a] 
WithTrailVal [PerPoint a] 

Instances

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

Defined in Types

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

Defined in Types

Generic (PerCurve a) Source # 
Instance details

Defined in Types

Associated Types

type Rep (PerCurve a) 
Instance details

Defined in Types

type Rep (PerCurve a) = D1 ('MetaData "PerCurve" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "CurrentVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PerPoint a])) :+: C1 ('MetaCons "WithTrailVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PerPoint a])))

Methods

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

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

Read a => Read (PerCurve a) Source # 
Instance details

Defined in Types

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

Defined in Types

Methods

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

show :: PerCurve a -> String #

showList :: [PerCurve a] -> ShowS #

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

Defined in Types

Methods

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

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

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

Defined in Types

Methods

compare :: PerCurve a -> PerCurve a -> Ordering #

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

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

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

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

max :: PerCurve a -> PerCurve a -> PerCurve a #

min :: PerCurve a -> PerCurve a -> PerCurve a #

type Rep (PerCurve a) Source # 
Instance details

Defined in Types

type Rep (PerCurve a) = D1 ('MetaData "PerCurve" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "CurrentVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PerPoint a])) :+: C1 ('MetaCons "WithTrailVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PerPoint a])))

data Period Source #

Instances

Instances details
FromJSON Period Source # 
Instance details

Defined in Types

ToJSON Period Source # 
Instance details

Defined in Types

Generic Period Source # 
Instance details

Defined in Types

Associated Types

type Rep Period 
Instance details

Defined in Types

type Rep Period = D1 ('MetaData "Period" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Daily" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Weekly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BiWeekly" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Monthly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Quarterly" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SemiAnnually" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Annually" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: Period -> Rep Period x #

to :: Rep Period x -> Period #

Show Period Source # 
Instance details

Defined in Types

Eq Period Source # 
Instance details

Defined in Types

Methods

(==) :: Period -> Period -> Bool #

(/=) :: Period -> Period -> Bool #

Ord Period Source # 
Instance details

Defined in Types

ToSchema Period Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep Period Source # 
Instance details

Defined in Types

type Rep Period = D1 ('MetaData "Period" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Daily" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Weekly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BiWeekly" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Monthly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Quarterly" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SemiAnnually" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Annually" 'PrefixI 'False) (U1 :: Type -> Type))))

data Threshold Source #

Constructors

Below 
EqBelow 
Above 
EqAbove 

Instances

Instances details
FromJSON Threshold Source # 
Instance details

Defined in Types

FromJSONKey Threshold Source # 
Instance details

Defined in Types

ToJSON Threshold Source # 
Instance details

Defined in Types

ToJSONKey Threshold Source # 
Instance details

Defined in Types

Generic Threshold Source # 
Instance details

Defined in Types

Associated Types

type Rep Threshold 
Instance details

Defined in Types

type Rep Threshold = D1 ('MetaData "Threshold" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Below" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqBelow" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Above" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqAbove" 'PrefixI 'False) (U1 :: Type -> Type)))
Read Threshold Source # 
Instance details

Defined in Types

Show Threshold Source # 
Instance details

Defined in Types

Eq Threshold Source # 
Instance details

Defined in Types

Ord Threshold Source # 
Instance details

Defined in Types

type Rep Threshold Source # 
Instance details

Defined in Types

type Rep Threshold = D1 ('MetaData "Threshold" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Below" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqBelow" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Above" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqAbove" 'PrefixI 'False) (U1 :: Type -> Type)))

data RangeType Source #

Constructors

II

include both start and end date

IE

include start date ,but not end date

EI

exclude start date but include end date

EE

exclude either start date and end date

NO_IE

no handling on start date and end date

Instances

Instances details
FromJSON RangeType Source # 
Instance details

Defined in Types

ToJSON RangeType Source # 
Instance details

Defined in Types

Generic RangeType Source # 
Instance details

Defined in Types

Associated Types

type Rep RangeType 
Instance details

Defined in Types

type Rep RangeType = D1 ('MetaData "RangeType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "II" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EI" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NO_IE" 'PrefixI 'False) (U1 :: Type -> Type))))
Read RangeType Source # 
Instance details

Defined in Types

Show RangeType Source # 
Instance details

Defined in Types

Eq RangeType Source # 
Instance details

Defined in Types

Ord RangeType Source # 
Instance details

Defined in Types

type Rep RangeType Source # 
Instance details

Defined in Types

type Rep RangeType = D1 ('MetaData "RangeType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "II" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EI" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NO_IE" 'PrefixI 'False) (U1 :: Type -> Type))))

data CutoffType Source #

Constructors

Inc 
Exc 

Instances

Instances details
FromJSON CutoffType Source # 
Instance details

Defined in Types

ToJSON CutoffType Source # 
Instance details

Defined in Types

Generic CutoffType Source # 
Instance details

Defined in Types

Associated Types

type Rep CutoffType 
Instance details

Defined in Types

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

Defined in Types

Show CutoffType Source # 
Instance details

Defined in Types

Eq CutoffType Source # 
Instance details

Defined in Types

Ord CutoffType Source # 
Instance details

Defined in Types

ToSchema CutoffType Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep CutoffType Source # 
Instance details

Defined in Types

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

data DealStatus Source #

pricing methods for assets

Constructors

DealAccelerated (Maybe Date)

Deal is accelerated status with optinal accerlerated date

DealDefaulted (Maybe Date)

Deal is defaulted status with optinal default date

Amortizing

Deal is amortizing

Revolving

Deal is revolving

PreClosing DealStatus

Deal is not closed, but has a closing date

Warehousing (Maybe DealStatus)

Deal is not closed, but closing date is not determined yet

Called

Deal is called

Ended Date

Deal is marked as closed

Instances

Instances details
FromJSON DealStatus Source # 
Instance details

Defined in Types

ToJSON DealStatus Source # 
Instance details

Defined in Types

Generic DealStatus Source # 
Instance details

Defined in Types

Associated Types

type Rep DealStatus 
Instance details

Defined in Types

Read DealStatus Source # 
Instance details

Defined in Types

Show DealStatus Source # 
Instance details

Defined in Types

Eq DealStatus Source # 
Instance details

Defined in Types

Ord DealStatus Source # 
Instance details

Defined in Types

type Rep DealStatus Source # 
Instance details

Defined in Types

data Index Source #

Instances

Instances details
FromJSON Index Source # 
Instance details

Defined in Types

ToJSON Index Source # 
Instance details

Defined in Types

Generic Index Source # 
Instance details

Defined in Types

Associated Types

type Rep Index 
Instance details

Defined in Types

type Rep Index = D1 ('MetaData "Index" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "LPR5Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LPR1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LIBOR1M" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LIBOR3M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LIBOR6M" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LIBOR1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY1Y" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "USTSY2Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "USTSY3Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY5Y" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "USTSY7Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY10Y" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "USTSY20Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY30Y" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "USCMT1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PRIME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COFI" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SOFR1M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SOFR3M" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SOFR6M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SOFR1Y" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EURIBOR1M" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EURIBOR3M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EURIBOR6M" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EURIBOR12M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BBSW" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IRPH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SONIA" 'PrefixI 'False) (U1 :: Type -> Type))))))

Methods

from :: Index -> Rep Index x #

to :: Rep Index x -> Index #

Read Index Source # 
Instance details

Defined in Types

Show Index Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Eq Index Source # 
Instance details

Defined in Types

Methods

(==) :: Index -> Index -> Bool #

(/=) :: Index -> Index -> Bool #

Ord Index Source # 
Instance details

Defined in Types

Methods

compare :: Index -> Index -> Ordering #

(<) :: Index -> Index -> Bool #

(<=) :: Index -> Index -> Bool #

(>) :: Index -> Index -> Bool #

(>=) :: Index -> Index -> Bool #

max :: Index -> Index -> Index #

min :: Index -> Index -> Index #

ToSchema Index Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep Index Source # 
Instance details

Defined in Types

type Rep Index = D1 ('MetaData "Index" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "LPR5Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LPR1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LIBOR1M" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LIBOR3M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LIBOR6M" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LIBOR1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY1Y" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "USTSY2Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "USTSY3Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY5Y" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "USTSY7Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY10Y" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "USTSY20Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "USTSY30Y" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "USCMT1Y" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PRIME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COFI" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SOFR1M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SOFR3M" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SOFR6M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SOFR1Y" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EURIBOR1M" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EURIBOR3M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EURIBOR6M" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EURIBOR12M" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BBSW" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IRPH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SONIA" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Cmp Source #

Constructors

G

Greater than

GE

Greater Equal than

L

Less than

LE

Less Equal than

E

Equals to

Instances

Instances details
FromJSON Cmp Source # 
Instance details

Defined in Types

ToJSON Cmp Source # 
Instance details

Defined in Types

Generic Cmp Source # 
Instance details

Defined in Types

Associated Types

type Rep Cmp 
Instance details

Defined in Types

type Rep Cmp = D1 ('MetaData "Cmp" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "G" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "E" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: Cmp -> Rep Cmp x #

to :: Rep Cmp x -> Cmp #

Read Cmp Source # 
Instance details

Defined in Types

Show Cmp Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Cmp -> ShowS #

show :: Cmp -> String #

showList :: [Cmp] -> ShowS #

Eq Cmp Source # 
Instance details

Defined in Types

Methods

(==) :: Cmp -> Cmp -> Bool #

(/=) :: Cmp -> Cmp -> Bool #

Ord Cmp Source # 
Instance details

Defined in Types

Methods

compare :: Cmp -> Cmp -> Ordering #

(<) :: Cmp -> Cmp -> Bool #

(<=) :: Cmp -> Cmp -> Bool #

(>) :: Cmp -> Cmp -> Bool #

(>=) :: Cmp -> Cmp -> Bool #

max :: Cmp -> Cmp -> Cmp #

min :: Cmp -> Cmp -> Cmp #

type Rep Cmp Source # 
Instance details

Defined in Types

type Rep Cmp = D1 ('MetaData "Cmp" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "G" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "E" 'PrefixI 'False) (U1 :: Type -> Type))))

type Date = Day Source #

type Dates = [Day] Source #

class TimeSeries ts where Source #

different types of curves, which determine how to interpolate between two points

Minimal complete definition

getDate

Methods

cmp :: ts -> ts -> Ordering Source #

sameDate :: ts -> ts -> Bool Source #

getDate :: ts -> Date Source #

getDates :: [ts] -> [Date] Source #

filterByDate :: [ts] -> Date -> [ts] Source #

sliceBy :: RangeType -> StartDate -> EndDate -> [ts] -> [ts] Source #

cutBy :: CutoffType -> DateDirection -> Date -> [ts] -> [ts] Source #

cmpWith :: ts -> Date -> Ordering Source #

isAfter :: ts -> Date -> Bool Source #

isOnAfter :: ts -> Date -> Bool Source #

isBefore :: ts -> Date -> Bool Source #

isOnBefore :: ts -> Date -> Bool Source #

splitBy :: Date -> CutoffType -> [ts] -> ([ts], [ts]) Source #

getByDate :: Date -> [ts] -> Maybe ts Source #

Instances

Instances details
TimeSeries AccrualPeriod Source # 
Instance details

Defined in AssetClass.AssetBase

TimeSeries TsRow Source # 
Instance details

Defined in Cashflow

TimeSeries ActionOnDate Source # 
Instance details

Defined in Deal.DealBase

TimeSeries Txn Source # 
Instance details

Defined in Stmt

TimeSeries (TsPoint a) Source # 
Instance details

Defined in Types

type Lag = Int Source #

type Cap = Micro Source #

data SplitType Source #

deal level cumulative statistics

Instances

Instances details
Generic SplitType Source # 
Instance details

Defined in Types

Associated Types

type Rep SplitType 
Instance details

Defined in Types

type Rep SplitType = D1 ('MetaData "SplitType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "EqToLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqToRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EqToLeftKeepOne" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqToLeftKeepOnes" 'PrefixI 'False) (U1 :: Type -> Type)))
Show SplitType Source # 
Instance details

Defined in Types

Eq SplitType Source # 
Instance details

Defined in Types

type Rep SplitType Source # 
Instance details

Defined in Types

type Rep SplitType = D1 ('MetaData "SplitType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "EqToLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqToRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EqToLeftKeepOne" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqToLeftKeepOnes" 'PrefixI 'False) (U1 :: Type -> Type)))

data BookItem Source #

Instances

Instances details
FromJSON BookItem Source # 
Instance details

Defined in Types

ToJSON BookItem Source # 
Instance details

Defined in Types

Generic BookItem Source # 
Instance details

Defined in Types

Methods

from :: BookItem -> Rep BookItem x #

to :: Rep BookItem x -> BookItem #

Read BookItem Source # 
Instance details

Defined in Types

Show BookItem Source # 
Instance details

Defined in Types

Eq BookItem Source # 
Instance details

Defined in Types

type Rep BookItem Source # 
Instance details

Defined in Types

data BalanceSheetReport Source #

Constructors

BalanceSheetReport

snapshot date of the balance sheet

Instances

Instances details
FromJSON BalanceSheetReport Source # 
Instance details

Defined in Types

ToJSON BalanceSheetReport Source # 
Instance details

Defined in Types

Generic BalanceSheetReport Source # 
Instance details

Defined in Types

Associated Types

type Rep BalanceSheetReport 
Instance details

Defined in Types

type Rep BalanceSheetReport = D1 ('MetaData "BalanceSheetReport" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BalanceSheetReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "asset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "liability") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem)) :*: (S1 ('MetaSel ('Just "equity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "reportDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))))
Read BalanceSheetReport Source # 
Instance details

Defined in Types

Show BalanceSheetReport Source # 
Instance details

Defined in Types

Eq BalanceSheetReport Source # 
Instance details

Defined in Types

type Rep BalanceSheetReport Source # 
Instance details

Defined in Types

type Rep BalanceSheetReport = D1 ('MetaData "BalanceSheetReport" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BalanceSheetReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "asset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "liability") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem)) :*: (S1 ('MetaSel ('Just "equity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookItem) :*: S1 ('MetaSel ('Just "reportDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))))

data CashflowReport Source #

Instances

Instances details
FromJSON CashflowReport Source # 
Instance details

Defined in Types

ToJSON CashflowReport Source # 
Instance details

Defined in Types

Generic CashflowReport Source # 
Instance details

Defined in Types

Associated Types

type Rep CashflowReport 
Instance details

Defined in Types

Read CashflowReport Source # 
Instance details

Defined in Types

Show CashflowReport Source # 
Instance details

Defined in Types

Eq CashflowReport Source # 
Instance details

Defined in Types

type Rep CashflowReport Source # 
Instance details

Defined in Types

data RateAssumption Source #

Constructors

RateCurve Index Ts

a rate curve ,which value of rates depends on time

RateFlat Index IRate

a rate constant

Instances

Instances details
FromJSON RateAssumption Source # 
Instance details

Defined in Types

ToJSON RateAssumption Source # 
Instance details

Defined in Types

Generic RateAssumption Source # 
Instance details

Defined in Types

Show RateAssumption Source # 
Instance details

Defined in Types

type Rep RateAssumption Source # 
Instance details

Defined in Types

data Table a b Source #

Constructors

ThresholdTable [(a, b)] 

Instances

Instances details
(FromJSON a, FromJSON b) => FromJSON (Table a b) Source # 
Instance details

Defined in Types

(ToJSON a, ToJSON b) => ToJSON (Table a b) Source # 
Instance details

Defined in Types

Methods

toJSON :: Table a b -> Value #

toEncoding :: Table a b -> Encoding #

toJSONList :: [Table a b] -> Value #

toEncodingList :: [Table a b] -> Encoding #

omitField :: Table a b -> Bool #

Generic (Table a b) Source # 
Instance details

Defined in Types

Associated Types

type Rep (Table a b) 
Instance details

Defined in Types

type Rep (Table a b) = D1 ('MetaData "Table" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "ThresholdTable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(a, b)])))

Methods

from :: Table a b -> Rep (Table a b) x #

to :: Rep (Table a b) x -> Table a b #

(Read a, Read b) => Read (Table a b) Source # 
Instance details

Defined in Types

(Show a, Show b) => Show (Table a b) Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Table a b -> ShowS #

show :: Table a b -> String #

showList :: [Table a b] -> ShowS #

(Eq a, Eq b) => Eq (Table a b) Source # 
Instance details

Defined in Types

Methods

(==) :: Table a b -> Table a b -> Bool #

(/=) :: Table a b -> Table a b -> Bool #

(Ord a, Ord b) => Ord (Table a b) Source # 
Instance details

Defined in Types

Methods

compare :: Table a b -> Table a b -> Ordering #

(<) :: Table a b -> Table a b -> Bool #

(<=) :: Table a b -> Table a b -> Bool #

(>) :: Table a b -> Table a b -> Bool #

(>=) :: Table a b -> Table a b -> Bool #

max :: Table a b -> Table a b -> Table a b #

min :: Table a b -> Table a b -> Table a b #

type Rep (Table a b) Source # 
Instance details

Defined in Types

type Rep (Table a b) = D1 ('MetaData "Table" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "ThresholdTable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(a, b)])))

lookupTable :: Ord a => Table a b -> Direction -> (a -> Bool) -> Maybe b Source #

data Direction Source #

direction of the transaction, in terms of the book keeping

Constructors

Up 
Down 

Instances

Instances details
FromJSON Direction Source # 
Instance details

Defined in Types

ToJSON Direction Source # 
Instance details

Defined in Types

Generic Direction Source # 
Instance details

Defined in Types

Associated Types

type Rep Direction 
Instance details

Defined in Types

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

Defined in Types

Show Direction Source # 
Instance details

Defined in Types

Eq Direction Source # 
Instance details

Defined in Types

Ord Direction Source # 
Instance details

Defined in Types

ToSchema Direction Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep Direction Source # 
Instance details

Defined in Types

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

data Txn Source #

Constructors

BondTxn Date Balance Interest Principal IRate Cash DueInt DueIoI (Maybe Float) TxnComment

bond transaction record for interest and principal

AccTxn Date Balance Amount TxnComment

account transaction record

ExpTxn Date Balance Amount Balance TxnComment

expense transaction record

SupportTxn Date (Maybe Balance) Balance DueInt DuePremium Cash TxnComment

liquidity provider transaction record

IrsTxn Date Balance Amount IRate IRate Balance TxnComment

interest swap transaction record

EntryTxn Date Balance Amount TxnComment

ledger book entry

TrgTxn Date Bool TxnComment 

Instances

Instances details
TimeSeries Txn Source # 
Instance details

Defined in Stmt

FromJSON Txn Source # 
Instance details

Defined in Types

ToJSON Txn Source # 
Instance details

Defined in Types

Generic Txn Source # 
Instance details

Defined in Types

Associated Types

type Rep Txn 
Instance details

Defined in Types

type Rep Txn = D1 ('MetaData "Txn" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "BondTxn" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interest) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Principal) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueIoI) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Float)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "AccTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "ExpTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))))) :+: ((C1 ('MetaCons "SupportTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Balance)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DuePremium)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))) :+: C1 ('MetaCons "IrsTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "EntryTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "TrgTxn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))))

Methods

from :: Txn -> Rep Txn x #

to :: Rep Txn x -> Txn #

Read Txn Source # 
Instance details

Defined in Types

Show Txn Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Txn -> ShowS #

show :: Txn -> String #

showList :: [Txn] -> ShowS #

Eq Txn Source # 
Instance details

Defined in Types

Methods

(==) :: Txn -> Txn -> Bool #

(/=) :: Txn -> Txn -> Bool #

Ord Txn Source # 
Instance details

Defined in Stmt

Methods

compare :: Txn -> Txn -> Ordering #

(<) :: Txn -> Txn -> Bool #

(<=) :: Txn -> Txn -> Bool #

(>) :: Txn -> Txn -> Bool #

(>=) :: Txn -> Txn -> Bool #

max :: Txn -> Txn -> Txn #

min :: Txn -> Txn -> Txn #

type Rep Txn Source # 
Instance details

Defined in Types

type Rep Txn = D1 ('MetaData "Txn" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "BondTxn" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interest) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Principal) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueIoI) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Float)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "AccTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "ExpTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))))) :+: ((C1 ('MetaCons "SupportTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Balance)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DuePremium)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))) :+: C1 ('MetaCons "IrsTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "EntryTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "TrgTxn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))))

data TxnComment Source #

transaction record in each entity

Instances

Instances details
FromJSON TxnComment Source # 
Instance details

Defined in Types

ToJSON TxnComment Source # 
Instance details

Defined in Types

Generic TxnComment Source # 
Instance details

Defined in Types

Associated Types

type Rep TxnComment 
Instance details

Defined in Types

type Rep TxnComment = D1 ('MetaData "TxnComment" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((((C1 ('MetaCons "PayInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "PayYield" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "PayPrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "PayGroupPrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "PayGroupInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "WriteOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: (C1 ('MetaCons "FundWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "PayPrinResidual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))))) :+: (((C1 ('MetaCons "PayFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)) :+: C1 ('MetaCons "SeqPayFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]))) :+: (C1 ('MetaCons "PayFeeYield" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)) :+: C1 ('MetaCons "Transfer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName)))) :+: ((C1 ('MetaCons "TransferBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Limit))) :+: C1 ('MetaCons "BookLedgerBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "PoolInflow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource)) :+: C1 ('MetaCons "LiquidationProceeds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolId])))))) :+: ((((C1 ('MetaCons "LiquidationSupport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "LiquidationDraw" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LiquidationRepay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "LiquidationSupportInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: ((C1 ('MetaCons "BankInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SupportDraw" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) :+: (((C1 ('MetaCons "UsingDS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "SwapAccrue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SwapInSettle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "SwapOutSettle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "PurchaseAsset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "IssuanceProceeds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "TxnDirection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection)) :+: C1 ('MetaCons "TxnComments" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxnComment])))))))
Read TxnComment Source # 
Instance details

Defined in Types

Show TxnComment Source # 
Instance details

Defined in Types

Eq TxnComment Source # 
Instance details

Defined in Types

Ord TxnComment Source # 
Instance details

Defined in Types

type Rep TxnComment Source # 
Instance details

Defined in Types

type Rep TxnComment = D1 ('MetaData "TxnComment" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((((C1 ('MetaCons "PayInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "PayYield" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "PayPrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "PayGroupPrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "PayGroupInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "WriteOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: (C1 ('MetaCons "FundWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "PayPrinResidual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))))) :+: (((C1 ('MetaCons "PayFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)) :+: C1 ('MetaCons "SeqPayFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]))) :+: (C1 ('MetaCons "PayFeeYield" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FeeName)) :+: C1 ('MetaCons "Transfer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName)))) :+: ((C1 ('MetaCons "TransferBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Limit))) :+: C1 ('MetaCons "BookLedgerBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "PoolInflow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource)) :+: C1 ('MetaCons "LiquidationProceeds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolId])))))) :+: ((((C1 ('MetaCons "LiquidationSupport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "LiquidationDraw" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LiquidationRepay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "LiquidationSupportInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: ((C1 ('MetaCons "BankInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SupportDraw" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) :+: (((C1 ('MetaCons "UsingDS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "SwapAccrue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SwapInSettle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "SwapOutSettle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "PurchaseAsset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :+: C1 ('MetaCons "IssuanceProceeds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "TxnDirection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection)) :+: C1 ('MetaCons "TxnComments" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxnComment])))))))

data RoundingBy a Source #

Constructors

RoundCeil a 
RoundFloor a 

Instances

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

Defined in Types

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

Defined in Types

Generic (RoundingBy a) Source # 
Instance details

Defined in Types

Associated Types

type Rep (RoundingBy a) 
Instance details

Defined in Types

type Rep (RoundingBy a) = D1 ('MetaData "RoundingBy" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "RoundCeil" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "RoundFloor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

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

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

Read a => Read (RoundingBy a) Source # 
Instance details

Defined in Types

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

Defined in Types

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

Defined in Types

Methods

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

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

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

Defined in Types

ToSchema (RoundingBy IRate) Source # 
Instance details

Defined in AssetClass.AssetBase

type Rep (RoundingBy a) Source # 
Instance details

Defined in Types

type Rep (RoundingBy a) = D1 ('MetaData "RoundingBy" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "RoundCeil" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "RoundFloor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data DateDirection Source #

Constructors

Future 
Past 

Instances

Instances details
Generic DateDirection Source # 
Instance details

Defined in Types

Associated Types

type Rep DateDirection 
Instance details

Defined in Types

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

Defined in Types

Show DateDirection Source # 
Instance details

Defined in Types

type Rep DateDirection Source # 
Instance details

Defined in Types

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

data BookDirection Source #

Constructors

Credit 
Debit 

Instances

Instances details
FromJSON BookDirection Source # 
Instance details

Defined in Types

ToJSON BookDirection Source # 
Instance details

Defined in Types

Generic BookDirection Source # 
Instance details

Defined in Types

Associated Types

type Rep BookDirection 
Instance details

Defined in Types

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

Defined in Types

Show BookDirection Source # 
Instance details

Defined in Types

Eq BookDirection Source # 
Instance details

Defined in Types

Ord BookDirection Source # 
Instance details

Defined in Types

type Rep BookDirection Source # 
Instance details

Defined in Types

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

type IRR = Micro Source #

data DealCycle Source #

different status of the deal

Constructors

EndCollection

| collection period HERE collection action , waterfall action

EndCollectionWF

| collection period collection action HERE, waterfall action

BeginDistributionWF

| collection period collection action , HEREwaterfall action

EndDistributionWF

| collection period collection action , waterfall actionHERE

InWF

| collection period collection action , waterfall HERE action

Instances

Instances details
FromJSON DealCycle Source # 
Instance details

Defined in Types

FromJSONKey DealCycle Source # 
Instance details

Defined in Types

ToJSON DealCycle Source # 
Instance details

Defined in Types

ToJSONKey DealCycle Source # 
Instance details

Defined in Types

Generic DealCycle Source # 
Instance details

Defined in Types

Associated Types

type Rep DealCycle 
Instance details

Defined in Types

type Rep DealCycle = D1 ('MetaData "DealCycle" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "EndCollection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndCollectionWF" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeginDistributionWF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndDistributionWF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InWF" 'PrefixI 'False) (U1 :: Type -> Type))))
Read DealCycle Source # 
Instance details

Defined in Types

Show DealCycle Source # 
Instance details

Defined in Types

Eq DealCycle Source # 
Instance details

Defined in Types

Ord DealCycle Source # 
Instance details

Defined in Types

type Rep DealCycle Source # 
Instance details

Defined in Types

type Rep DealCycle = D1 ('MetaData "DealCycle" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "EndCollection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndCollectionWF" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeginDistributionWF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndDistributionWF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InWF" 'PrefixI 'False) (U1 :: Type -> Type))))

data Limit Source #

Constructors

DuePct Rate

up to % of total amount due

DueCapAmt Balance

up to $ amount

KeepBalAmt DealStats

pay till a certain amount remains in an account

DS DealStats

transfer with limit described by a DealStats | ClearLedger BookDirection String -- ^ when transfer, clear the ledger by transfer amount | ClearLedgerBySeq BookDirection [String] -- ^ clear a direction to a sequence of ledgers | BookLedger String -- ^ when transfer, book the ledger by the transfer amount

RemainBalPct Rate

pay till remain balance equals to a percentage of stats

TillTarget

transfer amount which make target account up reach reserve balanace

TillSource

transfer amount out till source account down back to reserve balance

Multiple Limit Float

factor of a limit

Instances

Instances details
FromJSON Limit Source # 
Instance details

Defined in Types

ToJSON Limit Source # 
Instance details

Defined in Types

Generic Limit Source # 
Instance details

Defined in Types

Methods

from :: Limit -> Rep Limit x #

to :: Rep Limit x -> Limit #

Read Limit Source # 
Instance details

Defined in Types

Show Limit Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

Eq Limit Source # 
Instance details

Defined in Types

Methods

(==) :: Limit -> Limit -> Bool #

(/=) :: Limit -> Limit -> Bool #

Ord Limit Source # 
Instance details

Defined in Types

Methods

compare :: Limit -> Limit -> Ordering #

(<) :: Limit -> Limit -> Bool #

(<=) :: Limit -> Limit -> Bool #

(>) :: Limit -> Limit -> Bool #

(>=) :: Limit -> Limit -> Bool #

max :: Limit -> Limit -> Limit #

min :: Limit -> Limit -> Limit #

type Rep Limit Source # 
Instance details

Defined in Types

data Pre Source #

Instances

Instances details
FromJSON Pre Source # 
Instance details

Defined in Types

ToJSON Pre Source # 
Instance details

Defined in Types

Generic Pre Source # 
Instance details

Defined in Types

Associated Types

type Rep Pre 
Instance details

Defined in Types

type Rep Pre = D1 ('MetaData "Pre" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "IfZero" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "If" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: (C1 ('MetaCons "IfRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro))) :+: (C1 ('MetaCons "IfCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) :+: C1 ('MetaCons "IfByPeriodCurve" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCurve Balance))))))) :+: ((C1 ('MetaCons "IfRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) :+: (C1 ('MetaCons "IfRateByPeriodCurve" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCurve Rate)))) :+: C1 ('MetaCons "IfIntCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))))) :+: (C1 ('MetaCons "IfInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "IfIntBetween" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: C1 ('MetaCons "IfIntIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))))) :+: (((C1 ('MetaCons "IfDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "IfDateBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))) :+: C1 ('MetaCons "IfDateIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dates)))) :+: (C1 ('MetaCons "IfBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "If2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "IfRate2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))))) :+: ((C1 ('MetaCons "IfInt2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: (C1 ('MetaCons "IfDealStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :+: C1 ('MetaCons "Always" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: (C1 ('MetaCons "IfNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pre)) :+: (C1 ('MetaCons "Any" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])) :+: C1 ('MetaCons "All" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])))))))

Methods

from :: Pre -> Rep Pre x #

to :: Rep Pre x -> Pre #

Read Pre Source # 
Instance details

Defined in Types

Show Pre Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Pre -> ShowS #

show :: Pre -> String #

showList :: [Pre] -> ShowS #

Eq Pre Source # 
Instance details

Defined in Types

Methods

(==) :: Pre -> Pre -> Bool #

(/=) :: Pre -> Pre -> Bool #

Ord Pre Source # 
Instance details

Defined in Types

Methods

compare :: Pre -> Pre -> Ordering #

(<) :: Pre -> Pre -> Bool #

(<=) :: Pre -> Pre -> Bool #

(>) :: Pre -> Pre -> Bool #

(>=) :: Pre -> Pre -> Bool #

max :: Pre -> Pre -> Pre #

min :: Pre -> Pre -> Pre #

type Rep Pre Source # 
Instance details

Defined in Types

type Rep Pre = D1 ('MetaData "Pre" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((((C1 ('MetaCons "IfZero" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "If" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: (C1 ('MetaCons "IfRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro))) :+: (C1 ('MetaCons "IfCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) :+: C1 ('MetaCons "IfByPeriodCurve" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCurve Balance))))))) :+: ((C1 ('MetaCons "IfRateCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))) :+: (C1 ('MetaCons "IfRateByPeriodCurve" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCurve Rate)))) :+: C1 ('MetaCons "IfIntCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))))) :+: (C1 ('MetaCons "IfInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "IfIntBetween" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: C1 ('MetaCons "IfIntIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))))) :+: (((C1 ('MetaCons "IfDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "IfDateBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date))) :+: C1 ('MetaCons "IfDateIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dates)))) :+: (C1 ('MetaCons "IfBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "If2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "IfRate2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))))) :+: ((C1 ('MetaCons "IfInt2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: (C1 ('MetaCons "IfDealStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :+: C1 ('MetaCons "Always" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: (C1 ('MetaCons "IfNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pre)) :+: (C1 ('MetaCons "Any" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])) :+: C1 ('MetaCons "All" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pre])))))))

class Liable lb where Source #

Instances

Instances details
Liable LiqFacility Source # 
Instance details

Defined in CreditEnhancement

Liable Fee Source # 
Instance details

Defined in Expense

Liable RateSwap Source # 
Instance details

Defined in Hedge

Liable SRT Source # 
Instance details

Defined in Hedge

Liable Bond Source # 
Instance details

Defined in Liability

data PoolId Source #

Constructors

PoolName String

pool name

PoolConsol

consolidate pool ( the only pool )

DealBondFlow DealName String Date Rate

bond flow from deal

Instances

Instances details
FromJSON PoolId Source # 
Instance details

Defined in Types

FromJSONKey PoolId Source #

different types of waterfall execution

Instance details

Defined in Types

ToJSON PoolId Source # 
Instance details

Defined in Types

ToJSONKey PoolId Source # 
Instance details

Defined in Types

Generic PoolId Source # 
Instance details

Defined in Types

Methods

from :: PoolId -> Rep PoolId x #

to :: Rep PoolId x -> PoolId #

Read PoolId Source # 
Instance details

Defined in Types

Show PoolId Source # 
Instance details

Defined in Types

Eq PoolId Source # 
Instance details

Defined in Types

Methods

(==) :: PoolId -> PoolId -> Bool #

(/=) :: PoolId -> PoolId -> Bool #

Ord PoolId Source # 
Instance details

Defined in Types

type Rep PoolId Source # 
Instance details

Defined in Types

lookupIntervalTable :: Ord a => Table a b -> Direction -> (a -> Bool) -> Maybe ((a, b), (a, b)) Source #

data CutoffFields Source #

Constructors

IssuanceBalance

pool issuance balance

HistoryRecoveries

cumulative recoveries

HistoryInterest

cumulative interest collected

HistoryPrepayment

cumulative prepayment collected

HistoryPrepaymentPentalty

cumulative prepayment collected

HistoryPrincipal

cumulative principal collected

HistoryRental

cumulative rental collected

HistoryDefaults

cumulative default balance

HistoryDelinquency

cumulative delinquency balance

HistoryLoss

cumulative loss/write-off balance

HistoryCash

cumulative cash

HistoryFeePaid 
AccruedInterest

accrued interest at closing

RuntimeCurrentPoolBalance

current pool balance

Instances

Instances details
FromJSON CutoffFields Source # 
Instance details

Defined in Types

FromJSONKey CutoffFields Source # 
Instance details

Defined in Types

ToJSON CutoffFields Source # 
Instance details

Defined in Types

ToJSONKey CutoffFields Source # 
Instance details

Defined in Types

Generic CutoffFields Source # 
Instance details

Defined in Types

Associated Types

type Rep CutoffFields 
Instance details

Defined in Types

type Rep CutoffFields = D1 ('MetaData "CutoffFields" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "IssuanceBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HistoryRecoveries" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryInterest" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HistoryPrepayment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryPrepaymentPentalty" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HistoryPrincipal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryRental" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HistoryDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HistoryDelinquency" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryLoss" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HistoryCash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryFeePaid" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccruedInterest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RuntimeCurrentPoolBalance" 'PrefixI 'False) (U1 :: Type -> Type)))))
Read CutoffFields Source # 
Instance details

Defined in Types

Show CutoffFields Source # 
Instance details

Defined in Types

NFData CutoffFields Source # 
Instance details

Defined in Types

Methods

rnf :: CutoffFields -> () #

Eq CutoffFields Source # 
Instance details

Defined in Types

Ord CutoffFields Source # 
Instance details

Defined in Types

type Rep CutoffFields Source # 
Instance details

Defined in Types

type Rep CutoffFields = D1 ('MetaData "CutoffFields" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "IssuanceBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HistoryRecoveries" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryInterest" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HistoryPrepayment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryPrepaymentPentalty" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HistoryPrincipal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryRental" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HistoryDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HistoryDelinquency" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryLoss" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HistoryCash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HistoryFeePaid" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccruedInterest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RuntimeCurrentPoolBalance" 'PrefixI 'False) (U1 :: Type -> Type)))))

data PriceResult Source #

Constructors

PriceResult Valuation PerFace WAL Duration Convexity AccruedInterest [Txn] 
AssetPrice Valuation WAL Duration Convexity AccruedInterest 
OASResult PriceResult [Valuation] Spread 
ZSpread Spread 
IrrResult IRR [Txn] 

Instances

Instances details
FromJSON PriceResult Source # 
Instance details

Defined in Types

ToJSON PriceResult Source # 
Instance details

Defined in Types

Generic PriceResult Source # 
Instance details

Defined in Types

Associated Types

type Rep PriceResult 
Instance details

Defined in Types

Show PriceResult Source # 
Instance details

Defined in Types

Eq PriceResult Source # 
Instance details

Defined in Types

type Rep PriceResult Source # 
Instance details

Defined in Types

data DealStats Source #

Constructors

CurrentBondBalance 
CurrentPoolBalance (Maybe [PoolId]) 
CurrentPoolBegBalance (Maybe [PoolId]) 
CurrentPoolDefaultedBalance 
CumulativePoolDefaultedBalance (Maybe [PoolId])

Depreciated, use PoolCumCollection

CumulativePoolRecoveriesBalance (Maybe [PoolId])

Depreciated, use PoolCumCollection

CumulativeNetLoss (Maybe [PoolId]) 
OriginalBondBalance 
OriginalBondBalanceOf [BondName] 
BondTotalFunding [BondName] 
OriginalPoolBalance (Maybe [PoolId]) 
DealIssuanceBalance (Maybe [PoolId]) 
UseCustomData String 
PoolCumCollection [PoolSource] (Maybe [PoolId]) 
PoolCumCollectionTill Int [PoolSource] (Maybe [PoolId]) 
PoolCurCollection [PoolSource] (Maybe [PoolId]) 
PoolCollectionStats Int [PoolSource] (Maybe [PoolId]) 
PoolWaSpread (Maybe [PoolId]) 
AllAccBalance 
AccBalance [AccName] 
LedgerBalance [String] 
LedgerBalanceBy BookDirection [String] 
LedgerTxnAmt [String] (Maybe TxnComment) 
ReserveBalance [AccName] 
ReserveGap [AccName] 
ReserveExcess [AccName] 
ReserveGapAt Date [AccName] 
ReserveExcessAt Date [AccName] 
FutureCurrentPoolBalance (Maybe [PoolId]) 
FutureCurrentSchedulePoolBalance (Maybe [PoolId]) 
FutureCurrentSchedulePoolBegBalance (Maybe [PoolId]) 
PoolScheduleCfPv PricingMethod (Maybe [PoolId]) 
FuturePoolScheduleCfPv Date PricingMethod (Maybe [PoolId]) 
FutureWaCurrentPoolBalance Date Date (Maybe [PoolId]) 
FutureCurrentPoolBegBalance (Maybe [PoolId]) 
FutureCurrentBondBalance Date 
CurrentBondBalanceOf [BondName] 
BondIntPaidAt Date BondName 
BondsIntPaidAt Date [BondName] 
BondPrinPaidAt Date BondName 
BondsPrinPaidAt Date [BondName] 
BondBalanceTarget [BondName] 
BondBalanceGap BondName 
BondBalanceGapAt Date BondName 
BondDuePrin [BondName] 
BondReturn BondName Balance [TsPoint Amount] 
FeePaidAmt [FeeName] 
FeeTxnAmt [FeeName] (Maybe TxnComment) 
BondTxnAmt [BondName] (Maybe TxnComment) 
AccTxnAmt [AccName] (Maybe TxnComment) 
FeeTxnAmtBy Date [FeeName] (Maybe TxnComment) 
BondTxnAmtBy Date [BondName] (Maybe TxnComment) 
AccTxnAmtBy Date [AccName] (Maybe TxnComment) 
FeesPaidAt Date [FeeName] 
CurrentDueBondInt [BondName] 
CurrentDueBondIntAt Int [BondName] 
CurrentDueBondIntOverInt [BondName] 
CurrentDueBondIntOverIntAt Int [BondName] 
CurrentDueBondIntTotal [BondName] 
CurrentDueBondIntTotalAt Int [BondName] 
CurrentDueFee [FeeName] 
LastBondIntPaid [BondName] 
LastBondPrinPaid [BondName] 
LastFeePaid [FeeName] 
LiqCredit [String] 
LiqBalance [String] 
RateCapNet String 
RateSwapNet String 
BondBalanceHistory Date Date 
PoolCollectionHistory PoolSource Date Date (Maybe [PoolId]) 
UnderlyingBondBalance (Maybe [BondName]) 
WeightedAvgCurrentPoolBalance Date Date (Maybe [PoolId]) 
WeightedAvgCurrentBondBalance Date Date [BondName] 
WeightedAvgOriginalPoolBalance Date Date (Maybe [PoolId]) 
WeightedAvgOriginalBondBalance Date Date [BondName] 
CustomData String Date 
DealStatBalance DealStatFields 
AmountRequiredForTargetIRR Double BondName 
CurrentPoolBorrowerNum (Maybe [PoolId]) 
FutureCurrentPoolBorrowerNum Date (Maybe [PoolId]) 
ProjCollectPeriodNum 
MonthsTillMaturity BondName 
DealStatInt DealStatFields 
TestRate DealStats Cmp Micro 
TestAny Bool [DealStats] 
TestAll Bool [DealStats] 
TestNot DealStats 
IsDealStatus DealStatus 
IsMostSenior BondName [BondName] 
IsPaidOff [BondName] 
IsFeePaidOff [String] 
IsLiqSupportPaidOff [String] 
IsRateSwapPaidOff [String] 
IsOutstanding [BondName] 
HasPassedMaturity [BondName] 
TriggersStatus DealCycle String 
DealStatBool DealStatFields 
PoolWaRate (Maybe PoolId) 
BondRate BondName 
CumulativeNetLossRatio (Maybe [PoolId]) 
FutureCurrentBondFactor Date 
FutureCurrentPoolFactor Date (Maybe [PoolId]) 
BondFactor 
BondFactorOf BondName 
CumulativePoolDefaultedRate (Maybe [PoolId]) 
CumulativePoolDefaultedRateTill Int (Maybe [PoolId]) 
PoolFactor (Maybe [PoolId]) 
BondWaRate [BondName] 
DealStatRate DealStatFields 
Factor DealStats Rational 
Multiply [DealStats] 
Max [DealStats] 
Min [DealStats] 
Sum [DealStats] 
Substract [DealStats] 
Subtract [DealStats] 
Excess [DealStats] 
Avg [DealStats] 
AvgRatio [DealStats] 
Divide DealStats DealStats 
DivideRatio DealStats DealStats 
Constant Rational 
FloorAndCap DealStats DealStats DealStats 
FloorWith DealStats DealStats 
FloorWithZero DealStats 
CapWith DealStats DealStats 
Abs DealStats 
Round DealStats (RoundingBy Rational) 

Instances

Instances details
FromJSON DealStats Source # 
Instance details

Defined in Types

ToJSON DealStats Source # 
Instance details

Defined in Types

Generic DealStats Source # 
Instance details

Defined in Types

Associated Types

type Rep DealStats 
Instance details

Defined in Types

type Rep DealStats = D1 ('MetaData "DealStats" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((((((C1 ('MetaCons "CurrentBondBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "CurrentPoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CurrentPoolDefaultedBalance" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CumulativePoolDefaultedBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CumulativePoolRecoveriesBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "CumulativeNetLoss" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "OriginalBondBalance" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "OriginalBondBalanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondTotalFunding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "OriginalPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "DealIssuanceBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: ((C1 ('MetaCons "UseCustomData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PoolCumCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "PoolCumCollectionTill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "PoolCurCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: ((((C1 ('MetaCons "PoolCollectionStats" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "PoolWaSpread" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "AllAccBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])))) :+: ((C1 ('MetaCons "LedgerBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "LedgerBalanceBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: (C1 ('MetaCons "LedgerTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))) :+: C1 ('MetaCons "ReserveBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]))))) :+: (((C1 ('MetaCons "ReserveGap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])) :+: C1 ('MetaCons "ReserveExcess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]))) :+: (C1 ('MetaCons "ReserveGapAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])) :+: C1 ('MetaCons "ReserveExcessAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])))) :+: ((C1 ('MetaCons "FutureCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentSchedulePoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "FutureCurrentSchedulePoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "PoolScheduleCfPv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PricingMethod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))))))) :+: (((((C1 ('MetaCons "FuturePoolScheduleCfPv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PricingMethod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "FutureWaCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "FutureCurrentPoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: ((C1 ('MetaCons "CurrentBondBalanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondIntPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "BondsIntPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondPrinPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))))) :+: (((C1 ('MetaCons "BondsPrinPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondBalanceTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "BondBalanceGap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)) :+: C1 ('MetaCons "BondBalanceGapAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)))) :+: ((C1 ('MetaCons "BondDuePrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondReturn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Amount])))) :+: (C1 ('MetaCons "FeePaidAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])) :+: C1 ('MetaCons "FeeTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))))))) :+: ((((C1 ('MetaCons "BondTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))) :+: C1 ('MetaCons "AccTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: (C1 ('MetaCons "FeeTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: C1 ('MetaCons "BondTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))))) :+: ((C1 ('MetaCons "AccTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: C1 ('MetaCons "FeesPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]))) :+: (C1 ('MetaCons "CurrentDueBondInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))))) :+: (((C1 ('MetaCons "CurrentDueBondIntOverInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntOverIntAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "CurrentDueBondIntTotal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntTotalAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "CurrentDueFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])) :+: C1 ('MetaCons "LastBondIntPaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "LastBondPrinPaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "LastFeePaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])))))))) :+: ((((((C1 ('MetaCons "LiqCredit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "LiqBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: (C1 ('MetaCons "RateCapNet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "RateSwapNet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "BondBalanceHistory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "PoolCollectionHistory" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "UnderlyingBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [BondName]))) :+: C1 ('MetaCons "WeightedAvgCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: (((C1 ('MetaCons "WeightedAvgCurrentBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: C1 ('MetaCons "WeightedAvgOriginalPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "WeightedAvgOriginalBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: C1 ('MetaCons "CustomData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: ((C1 ('MetaCons "DealStatBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "AmountRequiredForTargetIRR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "CurrentPoolBorrowerNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentPoolBorrowerNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: ((((C1 ('MetaCons "ProjCollectPeriodNum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonthsTillMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "DealStatInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "TestRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro))))) :+: ((C1 ('MetaCons "TestAny" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "TestAll" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "TestNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "IsDealStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus))))) :+: (((C1 ('MetaCons "IsMostSenior" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "IsPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "IsFeePaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "IsLiqSupportPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :+: ((C1 ('MetaCons "IsRateSwapPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "IsOutstanding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "HasPassedMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "TriggersStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealCycle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))) :+: (((((C1 ('MetaCons "DealStatBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "PoolWaRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PoolId)))) :+: (C1 ('MetaCons "BondRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)) :+: C1 ('MetaCons "CumulativeNetLossRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: ((C1 ('MetaCons "FutureCurrentBondFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "FutureCurrentPoolFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "BondFactor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BondFactorOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))))) :+: (((C1 ('MetaCons "CumulativePoolDefaultedRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CumulativePoolDefaultedRateTill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "PoolFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "BondWaRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "DealStatRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "Factor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :+: (C1 ('MetaCons "Multiply" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Max" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))))) :+: ((((C1 ('MetaCons "Min" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Sum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "Substract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Subtract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))) :+: ((C1 ('MetaCons "Excess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Avg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "AvgRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Divide" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))))) :+: (((C1 ('MetaCons "DivideRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Constant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :+: (C1 ('MetaCons "FloorAndCap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "FloorWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))) :+: ((C1 ('MetaCons "FloorWithZero" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "CapWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: (C1 ('MetaCons "Abs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Round" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RoundingBy Rational))))))))))
Read DealStats Source # 
Instance details

Defined in Types

Show DealStats Source # 
Instance details

Defined in Types

Eq DealStats Source # 
Instance details

Defined in Types

Ord DealStats Source # 
Instance details

Defined in Types

type Rep DealStats Source # 
Instance details

Defined in Types

type Rep DealStats = D1 ('MetaData "DealStats" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((((((C1 ('MetaCons "CurrentBondBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "CurrentPoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CurrentPoolDefaultedBalance" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CumulativePoolDefaultedBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CumulativePoolRecoveriesBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "CumulativeNetLoss" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "OriginalBondBalance" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "OriginalBondBalanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondTotalFunding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "OriginalPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "DealIssuanceBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: ((C1 ('MetaCons "UseCustomData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PoolCumCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "PoolCumCollectionTill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "PoolCurCollection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: ((((C1 ('MetaCons "PoolCollectionStats" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PoolSource]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "PoolWaSpread" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "AllAccBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])))) :+: ((C1 ('MetaCons "LedgerBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "LedgerBalanceBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BookDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: (C1 ('MetaCons "LedgerTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))) :+: C1 ('MetaCons "ReserveBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]))))) :+: (((C1 ('MetaCons "ReserveGap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])) :+: C1 ('MetaCons "ReserveExcess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]))) :+: (C1 ('MetaCons "ReserveGapAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])) :+: C1 ('MetaCons "ReserveExcessAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName])))) :+: ((C1 ('MetaCons "FutureCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentSchedulePoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "FutureCurrentSchedulePoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "PoolScheduleCfPv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PricingMethod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))))))) :+: (((((C1 ('MetaCons "FuturePoolScheduleCfPv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PricingMethod) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: C1 ('MetaCons "FutureWaCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "FutureCurrentPoolBegBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: ((C1 ('MetaCons "CurrentBondBalanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondIntPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "BondsIntPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondPrinPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))))) :+: (((C1 ('MetaCons "BondsPrinPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondBalanceTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "BondBalanceGap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)) :+: C1 ('MetaCons "BondBalanceGapAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)))) :+: ((C1 ('MetaCons "BondDuePrin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "BondReturn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsPoint Amount])))) :+: (C1 ('MetaCons "FeePaidAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])) :+: C1 ('MetaCons "FeeTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))))))) :+: ((((C1 ('MetaCons "BondTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment))) :+: C1 ('MetaCons "AccTxnAmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: (C1 ('MetaCons "FeeTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: C1 ('MetaCons "BondTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))))) :+: ((C1 ('MetaCons "AccTxnAmtBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccName]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxnComment)))) :+: C1 ('MetaCons "FeesPaidAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName]))) :+: (C1 ('MetaCons "CurrentDueBondInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))))) :+: (((C1 ('MetaCons "CurrentDueBondIntOverInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntOverIntAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "CurrentDueBondIntTotal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "CurrentDueBondIntTotalAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "CurrentDueFee" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])) :+: C1 ('MetaCons "LastBondIntPaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "LastBondPrinPaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "LastFeePaid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FeeName])))))))) :+: ((((((C1 ('MetaCons "LiqCredit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "LiqBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: (C1 ('MetaCons "RateCapNet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "RateSwapNet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "BondBalanceHistory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "PoolCollectionHistory" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolSource) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "UnderlyingBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [BondName]))) :+: C1 ('MetaCons "WeightedAvgCurrentPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: (((C1 ('MetaCons "WeightedAvgCurrentBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: C1 ('MetaCons "WeightedAvgOriginalPoolBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: (C1 ('MetaCons "WeightedAvgOriginalBondBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: C1 ('MetaCons "CustomData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)))) :+: ((C1 ('MetaCons "DealStatBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "AmountRequiredForTargetIRR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "CurrentPoolBorrowerNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "FutureCurrentPoolBorrowerNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))))) :+: ((((C1 ('MetaCons "ProjCollectPeriodNum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonthsTillMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))) :+: (C1 ('MetaCons "DealStatInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "TestRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cmp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro))))) :+: ((C1 ('MetaCons "TestAny" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "TestAll" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "TestNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "IsDealStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus))))) :+: (((C1 ('MetaCons "IsMostSenior" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "IsPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "IsFeePaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "IsLiqSupportPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :+: ((C1 ('MetaCons "IsRateSwapPaidOff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "IsOutstanding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName]))) :+: (C1 ('MetaCons "HasPassedMaturity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])) :+: C1 ('MetaCons "TriggersStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealCycle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))) :+: (((((C1 ('MetaCons "DealStatBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "PoolWaRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PoolId)))) :+: (C1 ('MetaCons "BondRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName)) :+: C1 ('MetaCons "CumulativeNetLossRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))))) :+: ((C1 ('MetaCons "FutureCurrentBondFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: C1 ('MetaCons "FutureCurrentPoolFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "BondFactor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BondFactorOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BondName))))) :+: (((C1 ('MetaCons "CumulativePoolDefaultedRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "CumulativePoolDefaultedRateTill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId])))) :+: (C1 ('MetaCons "PoolFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PoolId]))) :+: C1 ('MetaCons "BondWaRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BondName])))) :+: ((C1 ('MetaCons "DealStatRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatFields)) :+: C1 ('MetaCons "Factor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :+: (C1 ('MetaCons "Multiply" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Max" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))))) :+: ((((C1 ('MetaCons "Min" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Sum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "Substract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Subtract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])))) :+: ((C1 ('MetaCons "Excess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Avg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]))) :+: (C1 ('MetaCons "AvgRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats])) :+: C1 ('MetaCons "Divide" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))))) :+: (((C1 ('MetaCons "DivideRatio" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Constant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :+: (C1 ('MetaCons "FloorAndCap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: C1 ('MetaCons "FloorWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)))) :+: ((C1 ('MetaCons "FloorWithZero" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "CapWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats))) :+: (C1 ('MetaCons "Abs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Round" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RoundingBy Rational))))))))))

data PricingMethod Source #

pricing methods for bonds

Constructors

BalanceFactor Rate Rate
balance
to be multiply with rate1 and rate2 if status of asset is "performing" or "defaulted"
BalanceFactor2 Rate Rate Rate
balance
by performingdelinqdefault factor
DefaultedBalance Rate
balance
only liquidate defaulted balance
PV IRate Rate

discount factor, recovery pct on default

PVCurve Ts
CF
Pricing cashflow with a Curve
PvRate IRate
CF
Pricing cashflow with a constant rate
PvWal Ts 
PvByRef DealStats
CF
Pricing cashflow with a ref rate
Custom Rate

custom amount

Instances

Instances details
FromJSON PricingMethod Source # 
Instance details

Defined in Types

ToJSON PricingMethod Source # 
Instance details

Defined in Types

Generic PricingMethod Source # 
Instance details

Defined in Types

Associated Types

type Rep PricingMethod 
Instance details

Defined in Types

type Rep PricingMethod = D1 ('MetaData "PricingMethod" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "BalanceFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "BalanceFactor2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))) :+: (C1 ('MetaCons "DefaultedBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PV" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))) :+: ((C1 ('MetaCons "PVCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: C1 ('MetaCons "PvRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate))) :+: (C1 ('MetaCons "PvWal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: (C1 ('MetaCons "PvByRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))))))
Read PricingMethod Source # 
Instance details

Defined in Types

Show PricingMethod Source # 
Instance details

Defined in Types

Eq PricingMethod Source # 
Instance details

Defined in Types

Ord PricingMethod Source # 
Instance details

Defined in Types

type Rep PricingMethod Source # 
Instance details

Defined in Types

type Rep PricingMethod = D1 ('MetaData "PricingMethod" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "BalanceFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "BalanceFactor2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))) :+: (C1 ('MetaCons "DefaultedBalance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PV" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)))) :+: ((C1 ('MetaCons "PVCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: C1 ('MetaCons "PvRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate))) :+: (C1 ('MetaCons "PvWal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts)) :+: (C1 ('MetaCons "PvByRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats)) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate))))))

data CustomDataType Source #

Instances

Instances details
FromJSON CustomDataType Source # 
Instance details

Defined in Types

ToJSON CustomDataType Source # 
Instance details

Defined in Types

Generic CustomDataType Source # 
Instance details

Defined in Types

Associated Types

type Rep CustomDataType 
Instance details

Defined in Types

Read CustomDataType Source # 
Instance details

Defined in Types

Show CustomDataType Source # 
Instance details

Defined in Types

Eq CustomDataType Source # 
Instance details

Defined in Types

Ord CustomDataType Source # 
Instance details

Defined in Types

type Rep CustomDataType Source # 
Instance details

Defined in Types

data ResultComponent Source #

Constructors

CallAt Date

the date when deal called

DealStatusChangeTo Date DealStatus DealStatus String

record when & why status changed

BondOutstanding String Balance Balance

when deal ends,calculate oustanding principal balance

BondOutstandingInt String Balance Balance

when deal ends,calculate oustanding interest due

InspectBal Date DealStats Balance

A bal value from inspection

InspectInt Date DealStats Int

A int value from inspection

InspectRate Date DealStats Micro

A rate value from inspection

InspectBool Date DealStats Bool

A bool value from inspection

RunningWaterfall Date ActionWhen

running waterfall at a date

FinancialReport StartDate EndDate BalanceSheetReport CashflowReport 
InspectWaterfall Date (Maybe String) [DealStats] [String] 
ErrorMsg String 
WarningMsg String 
EndRun (Maybe Date) String

end of run with a message | SnapshotCashflow Date String CashFlowFrame

Instances

Instances details
FromJSON ResultComponent Source # 
Instance details

Defined in Types

ToJSON ResultComponent Source # 
Instance details

Defined in Types

Generic ResultComponent Source # 
Instance details

Defined in Types

Associated Types

type Rep ResultComponent 
Instance details

Defined in Types

type Rep ResultComponent = D1 ('MetaData "ResultComponent" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "CallAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "DealStatusChangeTo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "BondOutstanding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))))) :+: ((C1 ('MetaCons "BondOutstandingInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: C1 ('MetaCons "InspectBal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: (C1 ('MetaCons "InspectInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: C1 ('MetaCons "InspectRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro)))))) :+: ((C1 ('MetaCons "InspectBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "RunningWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ActionWhen)) :+: C1 ('MetaCons "FinancialReport" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartDate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndDate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BalanceSheetReport) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CashflowReport))))) :+: ((C1 ('MetaCons "InspectWaterfall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: C1 ('MetaCons "ErrorMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "WarningMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "EndRun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))
Show ResultComponent Source # 
Instance details

Defined in Types

Eq ResultComponent Source # 
Instance details

Defined in Types

type Rep ResultComponent Source # 
Instance details

Defined in Types

type Rep ResultComponent = D1 ('MetaData "ResultComponent" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "CallAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date)) :+: (C1 ('MetaCons "DealStatusChangeTo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "BondOutstanding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))))) :+: ((C1 ('MetaCons "BondOutstandingInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :+: C1 ('MetaCons "InspectBal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)))) :+: (C1 ('MetaCons "InspectInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: C1 ('MetaCons "InspectRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Micro)))))) :+: ((C1 ('MetaCons "InspectBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStats) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "RunningWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ActionWhen)) :+: C1 ('MetaCons "FinancialReport" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StartDate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EndDate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BalanceSheetReport) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CashflowReport))))) :+: ((C1 ('MetaCons "InspectWaterfall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DealStats]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :+: C1 ('MetaCons "ErrorMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "WarningMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "EndRun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Date)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

data DealStatType Source #

Constructors

RtnBalance 
RtnRate 
RtnBool 
RtnInt 

Instances

Instances details
Generic DealStatType Source # 
Instance details

Defined in Types

Associated Types

type Rep DealStatType 
Instance details

Defined in Types

type Rep DealStatType = D1 ('MetaData "DealStatType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "RtnBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtnRate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RtnBool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtnInt" 'PrefixI 'False) (U1 :: Type -> Type)))
Read DealStatType Source # 
Instance details

Defined in Types

Show DealStatType Source # 
Instance details

Defined in Types

Eq DealStatType Source # 
Instance details

Defined in Types

Ord DealStatType Source # 
Instance details

Defined in Types

type Rep DealStatType Source # 
Instance details

Defined in Types

type Rep DealStatType = D1 ('MetaData "DealStatType" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "RtnBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtnRate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RtnBool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtnInt" 'PrefixI 'False) (U1 :: Type -> Type)))

data ActionWhen Source #

Constructors

EndOfPoolCollection

waterfall executed at the end of pool collection

DistributionDay DealStatus

waterfall executed depends on deal status

CleanUp

waterfall exectued upon a clean up call

OnClosingDay

waterfall executed on deal closing day

DefaultDistribution

default waterfall executed

RampUp

ramp up

WithinTrigger String

waterfall executed within a trigger

CustomWaterfall String

custom waterfall

Instances

Instances details
FromJSON ActionWhen Source # 
Instance details

Defined in Types

FromJSONKey ActionWhen Source # 
Instance details

Defined in Types

ToJSON ActionWhen Source # 
Instance details

Defined in Types

ToJSONKey ActionWhen Source # 
Instance details

Defined in Types

Generic ActionWhen Source # 
Instance details

Defined in Types

Associated Types

type Rep ActionWhen 
Instance details

Defined in Types

type Rep ActionWhen = D1 ('MetaData "ActionWhen" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "EndOfPoolCollection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistributionDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus))) :+: (C1 ('MetaCons "CleanUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OnClosingDay" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DefaultDistribution" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RampUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WithinTrigger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "CustomWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))
Read ActionWhen Source # 
Instance details

Defined in Types

Show ActionWhen Source # 
Instance details

Defined in Types

Eq ActionWhen Source # 
Instance details

Defined in Types

Ord ActionWhen Source # 
Instance details

Defined in Types

type Rep ActionWhen Source # 
Instance details

Defined in Types

type Rep ActionWhen = D1 ('MetaData "ActionWhen" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (((C1 ('MetaCons "EndOfPoolCollection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistributionDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DealStatus))) :+: (C1 ('MetaCons "CleanUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OnClosingDay" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DefaultDistribution" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RampUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WithinTrigger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "CustomWaterfall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

data DealStatFields Source #

different types of deal stats

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

data MyRatio Source #

Instances

Instances details
ToJSON MyRatio Source # 
Instance details

Defined in Types

Show MyRatio Source # 
Instance details

Defined in Types

data HowToPay Source #

Constructors

ByProRata 
BySequential 

Instances

Instances details
FromJSON HowToPay Source # 
Instance details

Defined in Types

ToJSON HowToPay Source # 
Instance details

Defined in Types

Generic HowToPay Source # 
Instance details

Defined in Types

Associated Types

type Rep HowToPay 
Instance details

Defined in Types

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

Methods

from :: HowToPay -> Rep HowToPay x #

to :: Rep HowToPay x -> HowToPay #

Read HowToPay Source # 
Instance details

Defined in Types

Show HowToPay Source # 
Instance details

Defined in Types

Eq HowToPay Source # 
Instance details

Defined in Types

Ord HowToPay Source # 
Instance details

Defined in Types

type Rep HowToPay Source # 
Instance details

Defined in Types

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

data BondPricingMethod Source #

condition which can be evaluated to a boolean value

Instances

Instances details
FromJSON BondPricingMethod Source # 
Instance details

Defined in Types

ToJSON BondPricingMethod Source # 
Instance details

Defined in Types

Generic BondPricingMethod Source # 
Instance details

Defined in Types

Associated Types

type Rep BondPricingMethod 
Instance details

Defined in Types

type Rep BondPricingMethod = D1 ('MetaData "BondPricingMethod" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BondBalanceFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: (C1 ('MetaCons "PvBondByRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PvBondByCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))))
Read BondPricingMethod Source # 
Instance details

Defined in Types

Show BondPricingMethod Source # 
Instance details

Defined in Types

Eq BondPricingMethod Source # 
Instance details

Defined in Types

Ord BondPricingMethod Source # 
Instance details

Defined in Types

type Rep BondPricingMethod Source # 
Instance details

Defined in Types

type Rep BondPricingMethod = D1 ('MetaData "BondPricingMethod" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) (C1 ('MetaCons "BondBalanceFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: (C1 ('MetaCons "PvBondByRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rate)) :+: C1 ('MetaCons "PvBondByCurve" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ts))))

data InvestorAction Source #

Constructors

Buy 
Sell 

Instances

Instances details
Generic InvestorAction Source # 
Instance details

Defined in Types

Associated Types

type Rep InvestorAction 
Instance details

Defined in Types

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

Defined in Types

Show InvestorAction Source # 
Instance details

Defined in Types

Eq InvestorAction Source # 
Instance details

Defined in Types

Ord InvestorAction Source # 
Instance details

Defined in Types

type Rep InvestorAction Source # 
Instance details

Defined in Types

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

Orphan instances