module Quant.MonteCarlo (
MonteCarlo
, MonteCarloT
, runMC
, Discretize(..)
, OptionType(..)
)
where
import Quant.ContingentClaim
import Data.Random
import Control.Applicative
import Control.Monad.State
import Data.Functor.Identity
import Quant.Time
import Data.RVar
import Data.Foldable (foldl')
import System.Random.Mersenne.Pure64
import qualified Data.Map as Map
type MonteCarloT m s = StateT s (RVarT m)
type MonteCarlo s a = MonteCarloT Identity s a
runMC :: MonadRandom (StateT b Identity) => MonteCarlo s c
-> b
-> s
-> c
runMC mc randState initState = flip evalState randState $ sampleRVarTWith lift (evalStateT mc initState)
class Discretize a where
initialize :: Discretize a => a
-> MonteCarlo (MCObservables, Time) ()
evolve :: Discretize a => a
-> Time
-> Bool
-> MonteCarlo (MCObservables, Time) ()
evolve mdl t2 anti = do
(_, t1) <- get
let ms = maxStep mdl
unless (t2==t1) $
if timeDiff t1 t2 < ms then
evolve' mdl t2 anti
else do
evolve' mdl (timeOffset t1 ms) anti
evolve mdl t2 anti
discountState :: Discretize a => a -> Time -> MonteCarlo (MCObservables, Time) Double
discountState m t = return $ discount m t
discount :: Discretize a => a -> Time -> Double
forwardGen :: Discretize a => a -> Time -> MonteCarlo (MCObservables, Time) Double
evolve' :: Discretize a => a
-> Time
-> Bool
-> MonteCarlo (MCObservables, Time) ()
maxStep :: Discretize a => a -> Double
maxStep _ = 1/250
simulateState :: Discretize a =>
a
-> ContingentClaim
-> Int
-> Bool
-> MonteCarlo (MCObservables, Time) Double
simulateState modl (ContingentClaim ccb) trials anti = avg <$> replicateM trials singleTrial
where
singleTrial = initialize modl >>
process (0 :: Double) Map.empty ccb []
process discCFs obsMap c@(CCProcessor t mf:ccs) allcfs@(CashFlow cft amt:cfs) =
if t > cft then do
evolve modl cft anti
d <- discountState modl cft
process (discCFs+d*amt) obsMap c cfs
else do
evolve modl t anti
obs <- gets fst
let obsMap' = Map.insert t obs obsMap
case mf of
Nothing -> process discCFs obsMap' ccs allcfs
Just f -> let newCFs = map ($obsMap') f
insertCFList xs cfList = foldl' (flip insertCF) cfList xs in
process discCFs obsMap' ccs (insertCFList newCFs allcfs)
process discCFs obsMap (CCProcessor t mf:ccs) [] = do
evolve modl t anti
obs <- gets fst
let obsMap' = Map.insert t obs obsMap
case mf of
Nothing -> process discCFs obsMap' ccs []
Just f -> let newCFs = map ($obsMap') f
insertCFList xs cfList = foldl' (flip insertCF) cfList xs in
process discCFs obsMap' ccs (insertCFList newCFs [])
process discCFs obsMap [] (cf:cfs) = do
evolve modl (cfTime cf) anti
d <- discountState modl $ cfTime cf
process (discCFs+d*cfAmount cf) obsMap [] cfs
process discCFs _ _ _ = return $! discCFs
insertCF (CashFlow t amt) (CashFlow t' amt':cfs)
| t > t' = CashFlow t' amt' : insertCF (CashFlow t amt) cfs
| otherwise = CashFlow t amt : CashFlow t' amt' : cfs
insertCF cf [] = [cf]
avg v = sum v / fromIntegral trials
runSimulation :: (Discretize a,
MonadRandom (StateT b Identity)) =>
a
-> ContingentClaim
-> b
-> Int
-> Bool
-> Double
runSimulation modl ccs seed trials anti = runMC run seed (Observables [], Time 0)
where
run = simulateState modl ccs trials anti
runSimulationAnti :: (Discretize a,
MonadRandom (StateT b Identity)) =>
a -> ContingentClaim -> b -> Int -> Double
runSimulationAnti modl ccs seed trials = (runSim True + runSim False) / 2
where runSim = runSimulation modl ccs seed (trials `div` 2)
quickSim :: Discretize a => a -> ContingentClaim -> Int -> Double
quickSim mdl opts trials = runSimulation mdl opts (pureMT 500) trials False
quickSimAnti :: Discretize a => a -> ContingentClaim -> Int -> Double
quickSimAnti mdl opts trials = runSimulationAnti mdl opts (pureMT 500) trials