quantfin-0.2.0.0: Quant finance library in pure Haskell.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Quant.ContingentClaim

Contents

Synopsis

Types for modeling contingent claims.

newtype ContingentClaim a Source

Key type for building contingent claims. Monoid instance allows for trivial combinations of contingent claims.

Constructors

ContingentClaim 

Fields

unCC :: [CCProcessor a]
 

Instances

type ContingentClaim1 = forall a. Obs1 a => ContingentClaim a Source

Contingent claims with one observable.

type ContingentClaim2 = forall a. Obs2 a => ContingentClaim a Source

Contingent claims with two observables.

type ContingentClaim3 = forall a. Obs3 a => ContingentClaim a Source

Contingent claims with three observables.

type ContingentClaim4 = forall a. Obs4 a => ContingentClaim a Source

Contingent claims with four observables.

data CCProcessor a Source

Basic element of a ContingentClaim. Each element contains a Time. Each Time, the observables are stored in the map. Also, optionally a payout function may be applied at any time step.

Constructors

CCProcessor 

Fields

monitorTime :: Time
 
payoutFunc :: [Map Time a -> CashFlow]
 

data OptionType Source

Type for Put or Calls

Constructors

Put 
Call 

data CashFlow Source

A CashFlow is just a time and an amount.

Constructors

CashFlow 

Fields

cfTime :: Time
 
cfAmount :: Double
 

type CCBuilder w r a = WriterT w (Reader r) a Source

Options and option combinators

specify :: CCBuilder (ContingentClaim a) (Map Time a) CashFlow -> ContingentClaim a Source

Pulls a ContingentClaim out of the CCBuilder monad.

monitor :: Obs1 a => Time -> CCBuilder (ContingentClaim a) (Map Time a) Double Source

monitor gets the value of the first observable at a given time.

monitor1 :: Obs1 a => Time -> CCBuilder (ContingentClaim a) (Map Time a) Double Source

monitor1 gets the value of the first observable at a given time.

monitor2 :: Obs2 a => Time -> CCBuilder (ContingentClaim a) (Map Time a) Double Source

monitor2 gets the value of the second observable at a given time.

monitor3 :: Obs3 a => Time -> CCBuilder (ContingentClaim a) (Map Time a) Double Source

monitor3 gets the value of the third observable at a given time.

monitor4 :: Obs4 a => Time -> CCBuilder (ContingentClaim a) (Map Time a) Double Source

monitor4 gets the value of the fourth observable at a given time.

monitor5 :: Obs5 a => Time -> CCBuilder (ContingentClaim a) (Map Time a) Double Source

monitor5 gets the value of the fifth observable at a given time.

vanillaOption :: Obs1 a => OptionType -> Double -> Time -> ContingentClaim a Source

Takes an OptionType, a strike, and a time to maturity and generates a vanilla option.

binaryOption :: Obs1 a => OptionType -> Double -> Double -> Time -> ContingentClaim a Source

Takes an OptionType, a strike, a payout amount and a time to maturity and generates a vanilla option.

straddle :: Obs1 a => Double -> Time -> ContingentClaim a Source

A straddle is a put and a call with the same time to maturity / strike.

arithmeticAsianOption :: Obs1 a => OptionType -> Double -> [Time] -> Time -> ContingentClaim a Source

Takes an OptionType, a strike, observation times, time to maturity and generates an arithmetic Asian option.

geometricAsianOption :: Obs1 a => OptionType -> Double -> [Time] -> Time -> ContingentClaim a Source

Takes an OptionType, a strike, observation times, time to maturity and generates an arithmetic Asian option.

callSpread :: Obs1 a => Double -> Double -> Time -> ContingentClaim a Source

A call spread is a long position in a low-strike call and a short position in a high strike call.

putSpread :: Obs1 a => Double -> Double -> Time -> ContingentClaim a Source

A put spread is a long position in a high strike put and a short position in a low strike put.

forwardContract :: Obs1 a => Time -> ContingentClaim a Source

Takes a time to maturity and generates a forward contract.

zcb :: Time -> Double -> ContingentClaim a Source

Takes an amount and a time and generates a fixed cash flow.

fixedBond :: Double -> Double -> Double -> Int -> ContingentClaim a Source

Takes a face value, an interest rate, a payment frequency and makes a fixed bond

multiplier :: Double -> ContingentClaim a -> ContingentClaim a Source

Scales up a contingent claim by a multiplier.

short :: ContingentClaim a -> ContingentClaim a Source

Flips the signs in a contingent claim to make it a short position.

combine :: ContingentClaim a -> ContingentClaim a -> ContingentClaim a Source

Combines two contingent claims into one.

terminalOnly :: Obs1 a => Time -> (Double -> Double) -> ContingentClaim a Source

Takes a maturity time and a function and generates a ContingentClaim dependent only on the terminal value of the observable.