module Quant.Models.Merton (
Merton (..)
) where
import Quant.Time
import Data.Random
import Data.Random.Distribution.Poisson
import Control.Monad.State
import Quant.MonteCarlo
import Quant.ContingentClaim
import Quant.YieldCurve
data Merton = forall a b . (YieldCurve a, YieldCurve b) => Merton {
mertonInitial :: Double
, mertonVol :: Double
, mertonIntensity :: Double
, mertonJumpMean :: Double
, mertonJumpVol :: Double
, mertonForwardGen :: a
, mertonDiscounter :: b }
instance Discretize Merton where
initialize (Merton s _ _ _ _ _ _) = put (Observables [s], Time 0)
evolve' m@(Merton _ vol intensity mu sig _ _) t2 anti = do
(Observables (stateVal:_), t1) <- get
fwd <- forwardGen m t2
let correction = exp (mu + sig*sig /2.0) 1
grwth = (fwd vol*vol/2 intensity * correction) * t
t = timeDiff t1 t2
normResid1 <- lift stdNormal
normResid2 <- lift stdNormal
poissonResid <- lift $ integralPoisson (intensity * t) :: MonteCarlo (MCObservables, Time) Int
let poisson' = fromIntegral poissonResid
jumpterm = mu*poisson'+sig*sqrt poisson' * normResid2
s' | anti = stateVal * exp (grwth normResid1*vol + jumpterm)
| otherwise = stateVal * exp (grwth + normResid1*vol + jumpterm)
put (Observables [s'], t2)
discount (Merton _ _ _ _ _ _ dsc) t = disc dsc t
forwardGen (Merton _ _ _ _ _ fg _) t2 = do
t1 <- gets snd
return $ forward fg t1 t2