Copyright | Copyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Tested with: GHC 8.0.1
The module defines the Parameter
monad transformer that allows representing the model
parameters. For example, they can be used when running the Monte-Carlo simulation.
In general, this monad is very useful for representing a computation which is external relative to the model itself.
Synopsis
- newtype Parameter m a = Parameter (Run m -> m a)
- class ParameterLift t m where
- liftParameter :: Parameter m a -> t m a
- invokeParameter :: Run m -> Parameter m a -> m a
- runParameter :: MonadDES m => Parameter m a -> Specs m -> m a
- runParameters :: MonadDES m => Parameter m a -> Specs m -> Int -> [m a]
- catchParameter :: (MonadException m, Exception e) => Parameter m a -> (e -> Parameter m a) -> Parameter m a
- finallyParameter :: MonadException m => Parameter m a -> Parameter m b -> Parameter m a
- throwParameter :: (MonadException m, Exception e) => e -> Parameter m a
- simulationIndex :: Monad m => Parameter m Int
- simulationCount :: Monad m => Parameter m Int
- simulationSpecs :: Monad m => Parameter m (Specs m)
- simulationEventQueue :: Monad m => Parameter m (EventQueue m)
- starttime :: Monad m => Parameter m Double
- stoptime :: Monad m => Parameter m Double
- dt :: Monad m => Parameter m Double
- generatorParameter :: Monad m => Parameter m (Generator m)
- memoParameter :: (MonadComp m, MonadIO m, MonadMask m) => Parameter m a -> m (Parameter m a)
- tableParameter :: Monad m => Array Int a -> Parameter m a
Parameter
newtype Parameter m a Source #
The Parameter
monad that allows specifying the model parameters.
For example, they can be used when running the Monte-Carlo simulation.
In general, this monad is very useful for representing a computation which is external relative to the model itself.
Instances
class ParameterLift t m where Source #
A type class to lift the parameters into other computations.
liftParameter :: Parameter m a -> t m a Source #
Lift the specified Parameter
computation into another computation.
Instances
runParameter :: MonadDES m => Parameter m a -> Specs m -> m a Source #
Run the parameter using the specified specs.
runParameters :: MonadDES m => Parameter m a -> Specs m -> Int -> [m a] Source #
Run the given number of parameters using the specified specs,
where each parameter is distinguished by its index parameterIndex
.
Error Handling
catchParameter :: (MonadException m, Exception e) => Parameter m a -> (e -> Parameter m a) -> Parameter m a Source #
Exception handling within Parameter
computations.
finallyParameter :: MonadException m => Parameter m a -> Parameter m b -> Parameter m a Source #
A computation with finalization part like the finally
function.
throwParameter :: (MonadException m, Exception e) => e -> Parameter m a Source #
Like the standard throw
function.
Predefined Parameters
simulationIndex :: Monad m => Parameter m Int Source #
Return the run index for the current simulation.
simulationCount :: Monad m => Parameter m Int Source #
Return the number of simulations currently run.
simulationEventQueue :: Monad m => Parameter m (EventQueue m) Source #
Return the event queue.
starttime :: Monad m => Parameter m Double Source #
Computation that returns the start simulation time.
stoptime :: Monad m => Parameter m Double Source #
Computation that returns the final simulation time.
generatorParameter :: Monad m => Parameter m (Generator m) Source #
Return the random number generator for the simulation run.
Memoization
memoParameter :: (MonadComp m, MonadIO m, MonadMask m) => Parameter m a -> m (Parameter m a) Source #
Memoize the Parameter
computation, always returning the same value
within a simulation run. However, the value will be recalculated for other
simulation runs. Also it is thread-safe when different simulation runs
are executed in parallel on physically different operating system threads.
Utilities
tableParameter :: Monad m => Array Int a -> Parameter m a Source #
Return a parameter which value is taken consequently from the specified table based on the run index of the current simulation starting from zero. After all values from the table are used, it takes again the first value of the table, then the second one and so on.