Safe Haskell | None |
---|---|
Language | Haskell2010 |
Lib
Synopsis
- type Amount = Balance
- type Rate = Rational
- type Dates = [Day]
- data Period
- type Balance = Centi
- type StartDate = Date
- type EndDate = Date
- daysBetween :: Date -> Date -> Integer
- daysBetweenI :: Date -> Date -> Int
- type Spread = Micro
- type Date = Day
- paySeqLiabilities :: Balance -> [Balance] -> [(Balance, Balance)]
- prorataFactors :: [Balance] -> Balance -> [Balance]
- afterNPeriod :: Day -> Integer -> Period -> Day
- data Ts
- = FloatCurve [TsPoint Rational]
- | BoolCurve [TsPoint Bool]
- | BalanceCurve [TsPoint Balance]
- | LeftBalanceCurve [TsPoint Balance]
- | RatioCurve [TsPoint Rational]
- | ThresholdCurve [TsPoint Rational]
- | IRateCurve [TsPoint IRate]
- | FactorCurveClosed [TsPoint Rational] Date
- | PricingCurve [TsPoint Rational]
- | PeriodCurve [TsPoint Int]
- | IntCurve [TsPoint Int]
- periodsBetween :: Day -> Day -> Period -> Integer
- periodRateFromAnnualRate :: Period -> IRate -> IRate
- type Floor = Micro
- type Cap = Micro
- data TsPoint a = TsPoint Date a
- toDate :: String -> Date
- toDates :: [String] -> [Date]
- genDates :: Date -> Period -> Int -> [Date]
- nextDate :: Date -> Period -> Date
- getValOnByDate :: Ts -> Date -> Balance
- getIntValOnByDate :: Ts -> Date -> Int
- sumValTs :: Ts -> Amount
- subTsBetweenDates :: Ts -> Maybe Date -> Maybe Date -> Ts
- splitTsByDate :: Ts -> Day -> (Ts, Ts)
- paySeqLiabilitiesAmt :: Balance -> [Balance] -> [Balance]
- getIntervalDays :: [Date] -> [Int]
- getIntervalFactors :: [Date] -> [Rate]
- zipWith8 :: (a -> b -> c -> d -> e -> f -> g -> h -> i) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i]
- zipWith9 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j]
- zipWith10 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] -> [k]
- zipWith11 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] -> [k] -> [l]
- zipWith12 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] -> [k] -> [l] -> [m]
- weightedBy :: [Rational] -> [Rational] -> Rational
- mkTs :: [(Date, Rational)] -> Ts
- mkRateTs :: [(Date, IRate)] -> Ts
- paySeqLiabResi :: Amount -> [Balance] -> [Amount]
Documentation
Instances
daysBetween :: Date -> Date -> Integer Source #
Given a start date and a end date, return number of days between(Integer)
daysBetweenI :: Date -> Date -> Int Source #
Given a start date and a end date, return number of days between(Int)
Constructors
FloatCurve [TsPoint Rational] | |
BoolCurve [TsPoint Bool] | |
BalanceCurve [TsPoint Balance] | |
LeftBalanceCurve [TsPoint Balance] | |
RatioCurve [TsPoint Rational] | |
ThresholdCurve [TsPoint Rational] | |
IRateCurve [TsPoint IRate] | |
FactorCurveClosed [TsPoint Rational] Date | |
PricingCurve [TsPoint Rational] | |
PeriodCurve [TsPoint Int] | |
IntCurve [TsPoint Int] |
Instances
FromJSON Ts Source # | |||||
ToJSON Ts Source # | |||||
Generic Ts Source # | |||||
Defined in Types Associated Types
| |||||
Read Ts Source # | |||||
Show Ts Source # | |||||
Eq Ts Source # | |||||
Ord Ts Source # | |||||
ToSchema Ts Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy Ts -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep Ts Source # | |||||
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])))))) |
Instances
TimeSeries (TsPoint a) Source # | |||||
Defined in Types Methods cmp :: TsPoint a -> TsPoint a -> Ordering Source # sameDate :: TsPoint a -> TsPoint a -> Bool Source # getDate :: TsPoint a -> Date Source # getDates :: [TsPoint a] -> [Date] Source # filterByDate :: [TsPoint a] -> Date -> [TsPoint a] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [TsPoint a] -> [TsPoint a] Source # cutBy :: CutoffType -> DateDirection -> Date -> [TsPoint a] -> [TsPoint a] Source # cmpWith :: TsPoint a -> Date -> Ordering Source # isAfter :: TsPoint a -> Date -> Bool Source # isOnAfter :: TsPoint a -> Date -> Bool Source # isBefore :: TsPoint a -> Date -> Bool Source # isOnBefore :: TsPoint a -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [TsPoint a] -> ([TsPoint a], [TsPoint a]) Source # getByDate :: Date -> [TsPoint a] -> Maybe (TsPoint a) Source # | |||||
FromJSON a => FromJSON (TsPoint a) Source # | |||||
ToJSON a => ToJSON (TsPoint a) Source # | |||||
Generic (TsPoint a) Source # | |||||
Defined in Types Associated Types
| |||||
Read a => Read (TsPoint a) Source # | |||||
Show a => Show (TsPoint a) Source # | |||||
Eq a => Eq (TsPoint a) Source # | |||||
Ord a => Ord (TsPoint a) Source # | |||||
ToSchema (TsPoint Balance) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Balance) -> Declare (Definitions Schema) NamedSchema # | |||||
ToSchema (TsPoint IRate) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint IRate) -> Declare (Definitions Schema) NamedSchema # | |||||
ToSchema (TsPoint Rational) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Rational) -> Declare (Definitions Schema) NamedSchema # | |||||
ToSchema (TsPoint Bool) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Bool) -> Declare (Definitions Schema) NamedSchema # | |||||
ToSchema (TsPoint Int) Source # | |||||
Defined in AssetClass.AssetBase Methods declareNamedSchema :: Proxy (TsPoint Int) -> Declare (Definitions Schema) NamedSchema # | |||||
type Rep (TsPoint a) Source # | |||||
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))) |
getIntervalDays :: [Date] -> [Int] Source #
getIntervalFactors :: [Date] -> [Rate] Source #
zipWith8 :: (a -> b -> c -> d -> e -> f -> g -> h -> i) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] Source #
zipWith9 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] Source #
zipWith10 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] -> [k] Source #
zipWith11 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] -> [k] -> [l] Source #
zipWith12 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -> [i] -> [j] -> [k] -> [l] -> [m] Source #