aivika-5.9.1: A multi-method simulation library
CopyrightCopyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Simulation.Aivika.Internal.Parameter

Description

Tested with: GHC 8.0.1

This is an internal implementation module that should never be used directly.

The module defines the Parameter monad 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

Parameter

newtype Parameter 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.

Constructors

Parameter (Run -> IO a) 

Instances

Instances details
Monad Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

(>>=) :: Parameter a -> (a -> Parameter b) -> Parameter b #

(>>) :: Parameter a -> Parameter b -> Parameter b #

return :: a -> Parameter a #

Functor Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

fmap :: (a -> b) -> Parameter a -> Parameter b #

(<$) :: a -> Parameter b -> Parameter a #

MonadFix Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

mfix :: (a -> Parameter a) -> Parameter a #

MonadFail Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

fail :: String -> Parameter a #

Applicative Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

pure :: a -> Parameter a #

(<*>) :: Parameter (a -> b) -> Parameter a -> Parameter b #

liftA2 :: (a -> b -> c) -> Parameter a -> Parameter b -> Parameter c #

(*>) :: Parameter a -> Parameter b -> Parameter b #

(<*) :: Parameter a -> Parameter b -> Parameter a #

MonadIO Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

liftIO :: IO a -> Parameter a #

MonadThrow Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

throwM :: Exception e => e -> Parameter a #

MonadCatch Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

catch :: Exception e => Parameter a -> (e -> Parameter a) -> Parameter a #

MonadMask Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

mask :: ((forall a. Parameter a -> Parameter a) -> Parameter b) -> Parameter b #

uninterruptibleMask :: ((forall a. Parameter a -> Parameter a) -> Parameter b) -> Parameter b #

generalBracket :: Parameter a -> (a -> ExitCase b -> Parameter c) -> (a -> Parameter b) -> Parameter (b, c) #

ParameterLift Parameter Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

ResultComputing Parameter Source # 
Instance details

Defined in Simulation.Aivika.Results

Eq (Parameter a) Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Methods

(==) :: Parameter a -> Parameter a -> Bool #

(/=) :: Parameter a -> Parameter a -> Bool #

Floating a => Floating (Parameter a) Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Fractional a => Fractional (Parameter a) Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Num a => Num (Parameter a) Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

Show (Parameter a) Source # 
Instance details

Defined in Simulation.Aivika.Internal.Parameter

ResultItemable (ResultValue a) => ResultProvider (Parameter a) Source # 
Instance details

Defined in Simulation.Aivika.Results

(Ix i, Show i, ResultItemable (ResultValue [e])) => ResultProvider (Parameter (Array i e)) Source # 
Instance details

Defined in Simulation.Aivika.Results

ResultItemable (ResultValue [e]) => ResultProvider (Parameter (Vector e)) Source # 
Instance details

Defined in Simulation.Aivika.Results

(ResultItemable (ResultValue a), ResultItemable (ResultValue (TimingStats a))) => ResultProvider (Parameter (TimingCounter a)) Source # 
Instance details

Defined in Simulation.Aivika.Results

(ResultItemable (ResultValue a), ResultItemable (ResultValue (SamplingStats a))) => ResultProvider (Parameter (SamplingCounter a)) Source # 
Instance details

Defined in Simulation.Aivika.Results

class ParameterLift m where Source #

A type class to lift the parameters to other computations.

Methods

liftParameter :: Parameter a -> m a Source #

Lift the specified Parameter computation to another computation.

invokeParameter :: Run -> Parameter a -> IO a Source #

Invoke the Parameter computation.

runParameter :: Parameter a -> Specs -> IO a Source #

Run the parameter using the specified specs.

runParameters :: Parameter a -> Specs -> Int -> [IO a] Source #

Run the given number of parameters using the specified specs, where each parameter is distinguished by its index parameterIndex.

Error Handling

catchParameter :: Exception e => Parameter a -> (e -> Parameter a) -> Parameter a Source #

Exception handling within Parameter computations.

finallyParameter :: Parameter a -> Parameter b -> Parameter a Source #

A computation with finalization part like the finally function.

throwParameter :: Exception e => e -> Parameter a Source #

Like the standard throw function.

Predefined Parameters

simulationIndex :: Parameter Int Source #

Return the run index for the current simulation.

simulationCount :: Parameter Int Source #

Return the number of simulations currently run.

simulationSpecs :: Parameter Specs Source #

Return the simulation specs.

starttime :: Parameter Double Source #

Computation that returns the start simulation time.

stoptime :: Parameter Double Source #

Computation that returns the final simulation time.

dt :: Parameter Double Source #

Computation that returns the integration time step.

generatorParameter :: Parameter Generator Source #

Return the random number generator for the simulation run.

Memoization

memoParameter :: Parameter a -> IO (Parameter 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 :: Array Int a -> Parameter 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.