module Quant.ContingentClaim (
ContingentClaim (..)
, CCProcessor (..)
, Observables (..)
, MCObservables
, OptionType (..)
, CashFlow (..)
, CCBuilder
, specify
, monitor
, monitorByNum
, vanillaOption
, binaryOption
, straddle
, arithmeticAsianOption
, geometricAsianOption
, callSpread
, putSpread
, forwardContract
, zcb
, fixedBond
, multiplier
, short
, combine
, terminalOnly
) where
import Control.Monad.Reader
import Control.Monad.Writer.Strict
import Quant.Types
import Quant.Time
import qualified Data.Map as M
type MCMap = M.Map Time MCObservables
type PayoffFunc a = MCMap -> a
data CCProcessor = CCProcessor {
monitorTime :: Time
, payoutFunc :: Maybe [PayoffFunc CashFlow]
}
type CCBuilder w r a = WriterT w (Reader r) a
monitor :: Time -> CCBuilder ContingentClaim MCMap Double
monitor = monitorByNum 0
monitorByNum :: Int -> Time -> CCBuilder ContingentClaim MCMap Double
monitorByNum idx t = do
tell $ ContingentClaim [CCProcessor t Nothing]
m <- lift ask
return $ obsGet (m M.! t) !! idx
specify :: CCBuilder ContingentClaim MCMap CashFlow -> ContingentClaim
specify x = w `mappend` ContingentClaim [CCProcessor (last0 w') (Just [f])]
where
w = runReader (execWriterT x) M.empty
f = runReader . liftM fst $ runWriterT x
w' = map monitorTime $ unCC w
last0 [] = Time 0
last0 [y] = y
last0 (_:ys) = last0 ys
newtype ContingentClaim = ContingentClaim { unCC :: [CCProcessor] }
instance Monoid ContingentClaim where
mempty = ContingentClaim []
mappend = combine
vanillaPayout :: OptionType
-> Double
-> Double
-> Double
vanillaPayout pc strike x = case pc of
Put -> max (strike x) 0
Call -> max (x strike) 0
binaryPayout :: OptionType
-> Double
-> Double
-> Double
-> Double
binaryPayout pc strike amount x = case pc of
Put -> if strike > x then amount else 0
Call -> if x > strike then amount else 0
terminalOnly :: Time -> (Double -> Double) -> ContingentClaim
terminalOnly t g = specify $ do
x <- monitor t
return $ CashFlow t $ g x
vanillaOption :: OptionType -> Double -> Time -> ContingentClaim
vanillaOption pc strike t = terminalOnly t $ vanillaPayout pc strike
binaryOption :: OptionType -> Double -> Double -> Time -> ContingentClaim
binaryOption pc strike amount t = terminalOnly t $ binaryPayout pc strike amount
arithmeticAsianOption :: OptionType -> Double -> [Time] -> Time -> ContingentClaim
arithmeticAsianOption pc strike obsTimes t = specify $ do
x <- mapM monitor obsTimes
let avg = sum x / fromIntegral (length obsTimes)
return $ CashFlow t $ vanillaPayout pc strike avg
geometricAsianOption :: OptionType -> Double -> [Time] -> Time -> ContingentClaim
geometricAsianOption pc strike obsTimes t = specify $ do
x <- mapM monitor obsTimes
let avg = product x ** (1 / fromIntegral (length obsTimes))
return $ CashFlow t $ vanillaPayout pc strike avg
multiplier :: Double -> ContingentClaim -> ContingentClaim
multiplier notional cs = ContingentClaim $ map f (unCC cs)
where f (CCProcessor t g) = CCProcessor t $ fmap (fmap (scale.)) g
scale (CashFlow dt amt) = CashFlow dt (amt*notional)
short :: ContingentClaim -> ContingentClaim
short = multiplier (1)
zcb :: Time -> Double -> ContingentClaim
zcb t amt = specify $ return $ CashFlow t amt
fixedBond :: Double -> Double -> Double -> Int -> ContingentClaim
fixedBond faceVal intRate freq pmts = zcb (Time $ fromIntegral pmts * freq) faceVal
<> mconcat (map f [1..pmts])
where
f x = zcb (Time $ fromIntegral x * freq) (faceVal * intRate * freq)
forwardContract :: Time -> ContingentClaim
forwardContract t = specify $ do
x <- monitor t
return $ CashFlow t x
callSpread :: Double -> Double -> Time -> ContingentClaim
callSpread lowStrike highStrike t = mappend (vanillaOption Call lowStrike t)
(short $ vanillaOption Call highStrike t)
putSpread :: Double -> Double -> Time -> ContingentClaim
putSpread lowStrike highStrike t = mappend (vanillaOption Put highStrike t)
(short $ vanillaOption Put lowStrike t)
straddle :: Double -> Time -> ContingentClaim
straddle strike t = vanillaOption Put strike t <> vanillaOption Call strike t
combine :: ContingentClaim -> ContingentClaim -> ContingentClaim
combine (ContingentClaim x) (ContingentClaim y) = ContingentClaim $ combine' x y
where
combine' (cc1:ccs1) (cc2:ccs2)
| monitorTime cc1 == monitorTime cc2 = let
(CCProcessor t mf) = cc1
(CCProcessor _ mf') = cc2 in
case mf of
Nothing -> cc2 : combine' ccs1 ccs2
Just a -> case mf' of
Nothing -> cc1 : combine' ccs1 ccs2
Just b -> CCProcessor t (Just (a ++ b)) : combine' ccs1 ccs2
| monitorTime cc1 > monitorTime cc2 = cc2 : combine' (cc1:ccs1) ccs2
| otherwise = cc1 : combine' ccs1 (cc2:ccs2)
combine' [] [] = []
combine' cs [] = cs
combine' [] cs = cs