aivika-experiment-5.2: Simulation experiments for the Aivika library

CopyrightCopyright (c) 2012-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Simulation.Aivika.Trans.Experiment.Types

Description

Tested with: GHC 8.0.1

The module defines the simulation experiments. They automate the process of generating and analyzing the results. Moreover, this module is open to extensions, allowing you to define your own output views for the simulation results, for example, such views that would allow saving the results in PDF or as charts. To decrease the number of dependencies, such possible extenstions are not included in this package, although simple views are provided.

Synopsis

Documentation

data Experiment m Source #

It defines the simulation experiment with the specified rendering backend and its bound data.

Constructors

Experiment 

Fields

defaultExperiment :: Experiment m Source #

The default experiment.

class ExperimentMonadProviding r m Source #

Allows specifying the experiment monad.

Associated Types

type ExperimentMonad r m :: * -> * Source #

Defines the experiment monad type.

type ExperimentMonadTry r m a = ExperimentMonad r m (Either SomeException a) Source #

Defines the experiment computation that tries to perform the calculation.

class ExperimentMonadProviding r m => ExperimentRendering r m where Source #

It allows rendering the simulation results in an arbitrary way.

Associated Types

data ExperimentContext r m :: * Source #

Defines a context used when rendering the experiment.

type ExperimentEnvironment r m :: * Source #

Defines the experiment environment.

Methods

prepareExperiment :: Experiment m -> r -> ExperimentMonad r m (ExperimentEnvironment r m) Source #

Prepare before rendering the experiment.

renderExperiment :: Experiment m -> r -> [ExperimentReporter r m] -> ExperimentEnvironment r m -> ExperimentMonad r m () Source #

Render the experiment after the simulation is finished, for example, creating the index.html file in the specified directory.

onExperimentCompleted :: Experiment m -> r -> ExperimentEnvironment r m -> ExperimentMonad r m () Source #

It is called when the experiment has been completed.

onExperimentFailed :: Exception e => Experiment m -> r -> ExperimentEnvironment r m -> e -> ExperimentMonad r m () Source #

It is called when the experiment rendering has failed.

data ExperimentGenerator r m Source #

This is a generator of the reporter with the specified rendering backend.

Constructors

ExperimentGenerator 

Fields

class ExperimentRendering r m => ExperimentView v r m where Source #

Defines a view in which the simulation results should be saved. You should extend this type class to define your own views such as the PDF document.

Minimal complete definition

outputView

Methods

outputView :: v m -> ExperimentGenerator r m Source #

Create a generator of the reporter.

data ExperimentData m Source #

It describes the source simulation data used in the experiment.

Constructors

ExperimentData 

Fields

data ExperimentReporter r m Source #

Defines what creates the simulation reports by the specified renderer.

Constructors

ExperimentReporter 

Fields

runExperiment_ Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> (m () -> ExperimentMonad r m a)

the function that actually starts the simulation run

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> ExperimentMonadTry r m () 

Run the simulation experiment sequentially.

runExperiment Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> (m () -> ExperimentMonad r m a)

the function that actually starts the simulation run

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> ExperimentMonadTry r m [a] 

Run the simulation experiment sequentially.

runExperimentWithExecutor Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> ([m ()] -> ExperimentMonad r m a)

an executor that allows parallelizing the simulation if required

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> ExperimentMonadTry r m a 

Run the simulation experiment with the specified executor.

runExperimentByIndex Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> (m () -> ExperimentMonad r m a)

the function that actually starts the simulation run

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> Int

the index of the current run (started from 1)

-> ExperimentMonadTry r m a 

Run the simulation experiment by the specified run index in series.

runExperimentByIndex_ Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> (m () -> ExperimentMonad r m a)

the function that actually starts the simulation run

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> Int

the index of the current run (started from 1)

-> ExperimentMonadTry r m () 

Run the simulation experiment by the specified run index in series.

runExperimentContByIndex Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> (m () -> ExperimentMonad r m (a, ExperimentMonad r m b))

the function that actually starts the simulation run and returns the corresponding continuation

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> Int

the index of the current run (started from 1)

-> ExperimentMonadTry r m (a, ExperimentMonadTry r m b) 

Run the simulation experiment by the specified run index in series returning the continuation of the actual computation.

runExperimentContByIndex_ Source #

Arguments

:: (MonadDES m, ExperimentRendering r m, Monad (ExperimentMonad r m), MonadException (ExperimentMonad r m)) 
=> (m () -> ExperimentMonad r m (a, ExperimentMonad r m b))

the function that actually starts the simulation run and returns the corresponding continuation

-> Experiment m

the simulation experiment to run

-> [ExperimentGenerator r m]

generators used for rendering

-> r

the rendering backend

-> Simulation m (Results m)

the simulation results received from the model

-> Int

the index of the current run (started from 1)

-> ExperimentMonadTry r m (a, ExperimentMonadTry r m ()) 

Run the simulation experiment by the specified run index in series returning the continuation of the actual computation.