| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Q.Types
Synopsis
- data Observables1 = Observables1 !Double
- data Observables2 = Observables2 !Double !Double
- data Observables3 = Observables3 !Double !Double !Double
- data Observables4 = Observables4 !Double !Double !Double !Double
- data Observables5 = Observables5 !Double !Double !Double !Double !Double
- data OptionType
- newtype Cash = Cash Double
- newtype Spot = Spot Double
- class Obs1 a where
- class Obs1 a => Obs2 a where
- class Obs2 a => Obs3 a where
- class Obs3 a => Obs4 a where
- class Obs4 a => Obs5 a where
- newtype Strike = Strike Double
- newtype Forward = Forward Double
- newtype Premium = Premium Double
- newtype Delta = Delta Double
- newtype Vega = Vega Double
- newtype Gamma = Gamma Double
- newtype Expiry = Expiry Day
- newtype YearFrac = YearFrac {
- unYearFrac :: Double
- newtype Rate = Rate Double
- newtype DF = DF Double
- newtype Vol = Vol Double
- newtype TotalVar = TotalVar Double
- class TimeScaleable a where
- cpi :: Num p => OptionType -> p
- discountFactor :: YearFrac -> Rate -> DF
- discount :: DF -> Double -> Double
- undiscount :: DF -> Double -> Double
- rateFromDiscount :: YearFrac -> DF -> Rate
- totalVarToVol :: TotalVar -> YearFrac -> Vol
- volToTotalVar :: Vol -> YearFrac -> TotalVar
- ($*$) :: (Coercible a Double, Coercible b Double) => a -> b -> a
- ($/$) :: (Coercible a Double, Coercible b Double) => a -> b -> a
- ($+$) :: (Coercible a Double, Coercible b Double) => a -> b -> a
Documentation
data Observables1 Source #
Single-observable container.
Constructors
| Observables1 !Double |
Instances
data Observables2 Source #
Two observable container.
Constructors
| Observables2 !Double !Double |
Instances
data Observables3 Source #
Three observable container.
Constructors
| Observables3 !Double !Double !Double |
Instances
data Observables4 Source #
Four observable container.
Constructors
| Observables4 !Double !Double !Double !Double |
Instances
data Observables5 Source #
Five observable container.
Instances
data OptionType Source #
Type for Put or Calls
Instances
Instances
| Eq Cash Source # | |
| Floating Cash Source # | |
| Fractional Cash Source # | |
| Num Cash Source # | |
| Ord Cash Source # | |
| Read Cash Source # | |
| Real Cash Source # | |
Defined in Q.Types Methods toRational :: Cash -> Rational # | |
| RealFloat Cash Source # | |
Defined in Q.Types Methods floatRadix :: Cash -> Integer # floatDigits :: Cash -> Int # floatRange :: Cash -> (Int, Int) # decodeFloat :: Cash -> (Integer, Int) # encodeFloat :: Integer -> Int -> Cash # significand :: Cash -> Cash # scaleFloat :: Int -> Cash -> Cash # isInfinite :: Cash -> Bool # isDenormalized :: Cash -> Bool # isNegativeZero :: Cash -> Bool # | |
| RealFrac Cash Source # | |
| Show Cash Source # | |
| Generic Cash Source # | |
| Storable Cash Source # | |
Defined in Q.Types | |
| FromField Cash Source # | |
| ToField Cash Source # | |
| type Rep Cash Source # | |
Instances
| Eq Spot Source # | |
| Floating Spot Source # | |
| Fractional Spot Source # | |
| Num Spot Source # | |
| Ord Spot Source # | |
| Read Spot Source # | |
| Real Spot Source # | |
Defined in Q.Types Methods toRational :: Spot -> Rational # | |
| RealFloat Spot Source # | |
Defined in Q.Types Methods floatRadix :: Spot -> Integer # floatDigits :: Spot -> Int # floatRange :: Spot -> (Int, Int) # decodeFloat :: Spot -> (Integer, Int) # encodeFloat :: Integer -> Int -> Spot # significand :: Spot -> Spot # scaleFloat :: Int -> Spot -> Spot # isInfinite :: Spot -> Bool # isDenormalized :: Spot -> Bool # isNegativeZero :: Spot -> Bool # | |
| RealFrac Spot Source # | |
| Show Spot Source # | |
| Generic Spot Source # | |
| Storable Spot Source # | |
Defined in Q.Types | |
| FromField Spot Source # | |
| ToField Spot Source # | |
| type Rep Spot Source # | |
Instances
class Obs1 a => Obs2 a where Source #
Instances
class Obs2 a => Obs3 a where Source #
Instances
class Obs3 a => Obs4 a where Source #
Instances
Instances
Instances
| Eq Forward Source # | |
| Floating Forward Source # | |
| Fractional Forward Source # | |
| Num Forward Source # | |
| Ord Forward Source # | |
| Read Forward Source # | |
| Real Forward Source # | |
Defined in Q.Types Methods toRational :: Forward -> Rational # | |
| RealFloat Forward Source # | |
Defined in Q.Types Methods floatRadix :: Forward -> Integer # floatDigits :: Forward -> Int # floatRange :: Forward -> (Int, Int) # decodeFloat :: Forward -> (Integer, Int) # encodeFloat :: Integer -> Int -> Forward # significand :: Forward -> Forward # scaleFloat :: Int -> Forward -> Forward # isInfinite :: Forward -> Bool # isDenormalized :: Forward -> Bool # isNegativeZero :: Forward -> Bool # | |
| RealFrac Forward Source # | |
| Show Forward Source # | |
| Generic Forward Source # | |
| Storable Forward Source # | |
| type Rep Forward Source # | |
Instances
| Eq Premium Source # | |
| Floating Premium Source # | |
| Fractional Premium Source # | |
| Num Premium Source # | |
| Ord Premium Source # | |
| Read Premium Source # | |
| Real Premium Source # | |
Defined in Q.Types Methods toRational :: Premium -> Rational # | |
| RealFloat Premium Source # | |
Defined in Q.Types Methods floatRadix :: Premium -> Integer # floatDigits :: Premium -> Int # floatRange :: Premium -> (Int, Int) # decodeFloat :: Premium -> (Integer, Int) # encodeFloat :: Integer -> Int -> Premium # significand :: Premium -> Premium # scaleFloat :: Int -> Premium -> Premium # isInfinite :: Premium -> Bool # isDenormalized :: Premium -> Bool # isNegativeZero :: Premium -> Bool # | |
| RealFrac Premium Source # | |
| Show Premium Source # | |
| Generic Premium Source # | |
| Storable Premium Source # | |
| FromField Premium Source # | |
| ToField Premium Source # | |
| type Rep Premium Source # | |
Instances
| Eq Delta Source # | |
| Floating Delta Source # | |
| Fractional Delta Source # | |
| Num Delta Source # | |
| Ord Delta Source # | |
| Read Delta Source # | |
| Real Delta Source # | |
Defined in Q.Types Methods toRational :: Delta -> Rational # | |
| RealFloat Delta Source # | |
Defined in Q.Types Methods floatRadix :: Delta -> Integer # floatDigits :: Delta -> Int # floatRange :: Delta -> (Int, Int) # decodeFloat :: Delta -> (Integer, Int) # encodeFloat :: Integer -> Int -> Delta # significand :: Delta -> Delta # scaleFloat :: Int -> Delta -> Delta # isInfinite :: Delta -> Bool # isDenormalized :: Delta -> Bool # isNegativeZero :: Delta -> Bool # | |
| RealFrac Delta Source # | |
| Show Delta Source # | |
| Generic Delta Source # | |
| Storable Delta Source # | |
| FromField Delta Source # | |
| ToField Delta Source # | |
| type Rep Delta Source # | |
Instances
| Eq Vega Source # | |
| Floating Vega Source # | |
| Fractional Vega Source # | |
| Num Vega Source # | |
| Ord Vega Source # | |
| Read Vega Source # | |
| Real Vega Source # | |
Defined in Q.Types Methods toRational :: Vega -> Rational # | |
| RealFloat Vega Source # | |
Defined in Q.Types Methods floatRadix :: Vega -> Integer # floatDigits :: Vega -> Int # floatRange :: Vega -> (Int, Int) # decodeFloat :: Vega -> (Integer, Int) # encodeFloat :: Integer -> Int -> Vega # significand :: Vega -> Vega # scaleFloat :: Int -> Vega -> Vega # isInfinite :: Vega -> Bool # isDenormalized :: Vega -> Bool # isNegativeZero :: Vega -> Bool # | |
| RealFrac Vega Source # | |
| Show Vega Source # | |
| Generic Vega Source # | |
| Storable Vega Source # | |
Defined in Q.Types | |
| FromField Vega Source # | |
| ToField Vega Source # | |
| type Rep Vega Source # | |
Instances
| Eq Gamma Source # | |
| Floating Gamma Source # | |
| Fractional Gamma Source # | |
| Num Gamma Source # | |
| Ord Gamma Source # | |
| Read Gamma Source # | |
| Real Gamma Source # | |
Defined in Q.Types Methods toRational :: Gamma -> Rational # | |
| RealFloat Gamma Source # | |
Defined in Q.Types Methods floatRadix :: Gamma -> Integer # floatDigits :: Gamma -> Int # floatRange :: Gamma -> (Int, Int) # decodeFloat :: Gamma -> (Integer, Int) # encodeFloat :: Integer -> Int -> Gamma # significand :: Gamma -> Gamma # scaleFloat :: Int -> Gamma -> Gamma # isInfinite :: Gamma -> Bool # isDenormalized :: Gamma -> Bool # isNegativeZero :: Gamma -> Bool # | |
| RealFrac Gamma Source # | |
| Show Gamma Source # | |
| Generic Gamma Source # | |
| Storable Gamma Source # | |
| FromField Gamma Source # | |
| ToField Gamma Source # | |
| type Rep Gamma Source # | |
Constructors
| YearFrac | |
Fields
| |
Instances
Instances
| Eq Rate Source # | |
| Floating Rate Source # | |
| Fractional Rate Source # | |
| Num Rate Source # | |
| Ord Rate Source # | |
| Read Rate Source # | |
| Real Rate Source # | |
Defined in Q.Types Methods toRational :: Rate -> Rational # | |
| RealFloat Rate Source # | |
Defined in Q.Types Methods floatRadix :: Rate -> Integer # floatDigits :: Rate -> Int # floatRange :: Rate -> (Int, Int) # decodeFloat :: Rate -> (Integer, Int) # encodeFloat :: Integer -> Int -> Rate # significand :: Rate -> Rate # scaleFloat :: Int -> Rate -> Rate # isInfinite :: Rate -> Bool # isDenormalized :: Rate -> Bool # isNegativeZero :: Rate -> Bool # | |
| RealFrac Rate Source # | |
| Show Rate Source # | |
| Generic Rate Source # | |
| Storable Rate Source # | |
Defined in Q.Types | |
| FromField Rate Source # | |
| ToField Rate Source # | |
| TimeScaleable Rate Source # | |
| type Rep Rate Source # | |
Instances
| Eq DF Source # | |
| Floating DF Source # | |
Defined in Q.Types Methods | |
| Fractional DF Source # | |
| Num DF Source # | |
| Ord DF Source # | |
| Read DF Source # | |
| Real DF Source # | |
Defined in Q.Types Methods toRational :: DF -> Rational # | |
| RealFloat DF Source # | |
Defined in Q.Types Methods floatRadix :: DF -> Integer # floatDigits :: DF -> Int # floatRange :: DF -> (Int, Int) # decodeFloat :: DF -> (Integer, Int) # encodeFloat :: Integer -> Int -> DF # significand :: DF -> DF # scaleFloat :: Int -> DF -> DF # isInfinite :: DF -> Bool # isDenormalized :: DF -> Bool # isNegativeZero :: DF -> Bool # | |
| RealFrac DF Source # | |
| Show DF Source # | |
| Generic DF Source # | |
| Storable DF Source # | |
| type Rep DF Source # | |
Instances
| Eq Vol Source # | |
| Floating Vol Source # | |
| Fractional Vol Source # | |
| Num Vol Source # | |
| Ord Vol Source # | |
| Read Vol Source # | |
| Real Vol Source # | |
Defined in Q.Types Methods toRational :: Vol -> Rational # | |
| RealFloat Vol Source # | |
Defined in Q.Types Methods floatRadix :: Vol -> Integer # floatDigits :: Vol -> Int # floatRange :: Vol -> (Int, Int) # decodeFloat :: Vol -> (Integer, Int) # encodeFloat :: Integer -> Int -> Vol # significand :: Vol -> Vol # scaleFloat :: Int -> Vol -> Vol # isInfinite :: Vol -> Bool # isDenormalized :: Vol -> Bool # isNegativeZero :: Vol -> Bool # | |
| RealFrac Vol Source # | |
| Show Vol Source # | |
| Generic Vol Source # | |
| Storable Vol Source # | |
Defined in Q.Types | |
| FromField Vol Source # | |
| ToField Vol Source # | |
| TimeScaleable Vol Source # | |
| InterpolatorV StrikeInterpolation Strike Vol Source # | |
Defined in Q.Options.ImpliedVol.StrikeInterpolation Methods interpolateV :: StrikeInterpolation -> SortedVector Strike -> Vector Vol -> Strike -> Vol Source # | |
| type Rep Vol Source # | |
(w(S_0, K, T) = sigma_{BS}(S_0, K, T)T )
Instances
class TimeScaleable a where Source #
Represents concepts that scale as a function of time such as Vol
Instances
cpi :: Num p => OptionType -> p Source #