Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type MonteCarlo s a = MonteCarloT Identity s a
- type MonteCarloT m s = StateT s (RVarT m)
- runMC :: MonadRandom (StateT b Identity) => MonteCarlo s c -> b -> s -> c
- class Discretize a b | a -> b where
- initialize :: Discretize a b => a -> MonteCarlo (b, Time) ()
- evolve :: Discretize a b => a -> Time -> Bool -> MonteCarlo (b, Time) ()
- discount :: Discretize a b => a -> Time -> MonteCarlo (b, Time) Double
- forwardGen :: Discretize a b => a -> Time -> MonteCarlo (b, Time) Double
- evolve' :: Discretize a b => a -> Time -> Bool -> MonteCarlo (b, Time) ()
- maxStep :: Discretize a b => a -> Double
- simulateState :: Discretize a b => a -> ContingentClaim b -> Int -> Bool -> MonteCarlo (b, Time) Double
- data OptionType
- runSimulation :: (Discretize a b, MonadRandom (StateT c Identity)) => a -> ContingentClaim b -> c -> Int -> Bool -> Double
- runSimulationAnti :: (Discretize a b, MonadRandom (StateT c Identity)) => a -> ContingentClaim b -> c -> Int -> Double
- quickSim :: Discretize a b => a -> ContingentClaim b -> Int -> Double
- quickSimAnti :: Discretize a b => a -> ContingentClaim b -> Int -> Double
The MonteCarlo type.
type MonteCarlo s a = MonteCarloT Identity s a Source
Wraps the Identity monad in the MonteCarloT
transformer.
type MonteCarloT m s = StateT s (RVarT m) Source
A monad transformer for Monte-Carlo calculations.
:: MonadRandom (StateT b Identity) | |
=> MonteCarlo s c | Monte Carlo computation. |
-> b | Initial state. |
-> s | Initial random-generator state. |
-> c | Final result of computation. |
Runs a MonteCarlo calculation and provides the result of the computation.
The discretize typeclass.
class Discretize a b | a -> b where Source
The Discretize
class defines those
models on which Monte Carlo simulations
can be performed.
Minimal complete definition: initialize
, discounter
, forwardGen
and evolve'
.
:: Discretize a b | |
=> a | Model |
-> MonteCarlo (b, Time) () |
Initializes a Monte Carlo simulation for a given number of runs.
:: Discretize a b | |
=> a | Model |
-> Time | time to evolve to |
-> Bool | |
-> MonteCarlo (b, Time) () |
Evolves the internal states of the MC variables between two times.
discount :: Discretize a b => a -> Time -> MonteCarlo (b, Time) Double Source
Non-stateful discounting function...might need to find a better place to put this.
forwardGen :: Discretize a b => a -> Time -> MonteCarlo (b, Time) Double Source
Stateful forward generator for a given model at a certain time.
:: Discretize a b | |
=> a | model |
-> Time | time to evolve to |
-> Bool | whether or not to use flipped variates |
-> MonteCarlo (b, Time) () | computation result |
Internal function to evolve a model to a given time.
maxStep :: Discretize a b => a -> Double Source
Determines the maximum size time-step for discretization purposes. Defaults to 1/250.
:: Discretize a b | |
=> a | model |
-> ContingentClaim b | compilied basket of claims |
-> Int | number of trials |
-> Bool | antithetic? |
-> MonteCarlo (b, Time) Double | computation result |
Perform a simulation of a compiled basket of contingent claims.
:: (Discretize a b, MonadRandom (StateT c Identity)) | |
=> a | model |
-> ContingentClaim b | claims to value |
-> c | initial random state |
-> Int | trials |
-> Bool | whether to use antithetic variables |
-> Double | final value |
Runs a simulation for a ContingentClaim
.
runSimulationAnti :: (Discretize a b, MonadRandom (StateT c Identity)) => a -> ContingentClaim b -> c -> Int -> Double Source
Like runSimulation
, but splits the trials in two and does antithetic variates.
quickSim :: Discretize a b => a -> ContingentClaim b -> Int -> Double Source
runSimulation
with a default random number generator.
quickSimAnti :: Discretize a b => a -> ContingentClaim b -> Int -> Double Source
runSimulationAnti
with a default random number generator.