module Quant.Models.Black (
Black (..)
) where
import Quant.Time
import Quant.YieldCurve
import Data.Random
import Control.Monad.State
import Quant.MonteCarlo
import Quant.ContingentClaim
data Black = forall a b . (YieldCurve a, YieldCurve b) => Black {
blackInit :: Double
, blackVol :: Double
, blackForwardGen :: a
, blackYieldCurve :: b }
instance Discretize Black where
initialize (Black s _ _ _) = put (Observables [s], Time 0)
evolve' b@(Black _ vol _ _) t2 anti = do
(Observables (stateVal:_), t1) <- get
fwd <- forwardGen b t2
let grwth = (fwd vol*vol/2) * timeDiff t1 t2
postVal <- do
resid <- lift stdNormal
if anti then
return $ stateVal * exp (grwth resid*vol)
else
return $ stateVal * exp (grwth + resid*vol)
put (Observables [postVal], t2)
discount (Black _ _ _ dsc) t = disc dsc t
forwardGen (Black _ _ fg _) t2 = do
(_, t1) <- get
return $ forward fg t1 t2
maxStep _ = 100