experimenter-0.1.0.12: Perform scientific experiments stored in a DB, and generate reports.
Safe HaskellNone
LanguageHaskell2010

Experimenter.Experiment

Synopsis

Documentation

data Phase Source #

Phase of experiment. Each experiment runs through all phases, where however a phase may have 0 steps.

Constructors

PreparationPhase

For preparing the evaluation. For instance to let a machine learning algorithm learn its function, before it is evaluated.

WarmUpPhase

The warm up phase is equal to the evaluation phase, but does not count as evaluation. Used to get the system in a steady state.

EvaluationPhase

Evaluation phase.

Instances

Instances details
Enum Phase Source # 
Instance details

Defined in Experimenter.Experiment

Eq Phase Source # 
Instance details

Defined in Experimenter.Experiment

Methods

(==) :: Phase -> Phase -> Bool #

(/=) :: Phase -> Phase -> Bool #

Ord Phase Source # 
Instance details

Defined in Experimenter.Experiment

Methods

compare :: Phase -> Phase -> Ordering #

(<) :: Phase -> Phase -> Bool #

(<=) :: Phase -> Phase -> Bool #

(>) :: Phase -> Phase -> Bool #

(>=) :: Phase -> Phase -> Bool #

max :: Phase -> Phase -> Phase #

min :: Phase -> Phase -> Phase #

Show Phase Source # 
Instance details

Defined in Experimenter.Experiment

Methods

showsPrec :: Int -> Phase -> ShowS #

show :: Phase -> String #

showList :: [Phase] -> ShowS #

class (Monad (ExpM a), MonadUnliftIO (ExpM a), NFData a, NFData (InputState a), NFData (InputValue a), Serialize (InputValue a), Serialize (InputState a), Serialize (Serializable a)) => ExperimentDef a where Source #

Definition of the Experiment.

Minimal complete definition

runStep

Associated Types

type ExpM a :: Type -> Type Source #

Monad to run experiments in. In most cases you want this to be IO.

type Serializable a :: Type Source #

Type that is used to serialize the current state.

type InputValue a :: Type Source #

The input to the system for running a step. Set to () if unused.

type InputState a :: Type Source #

Can be used to save a information from one call to generateInput to the next. Set to () if unused.

Methods

generateInput :: GenIO -> a -> InputState a -> Period -> ExpM a (InputValue a, InputState a) Source #

Generate some input values and possibly modify state. This function can be used to change the state. It is called before runStep and its output is used to call runStep.

default generateInput :: (InputValue a ~ (), InputState a ~ ()) => GenIO -> a -> InputState a -> Period -> ExpM a (InputValue a, InputState a) Source #

runStep :: Phase -> a -> InputValue a -> Period -> ExpM a ([StepResult], a) Source #

Run a step of the environment and return new state and result.

parameters :: a -> [ParameterSetup a] Source #

Provides the parameter setting. Parameters are used to design the experiment instances, e.g. the variants that will be run.

default parameters :: a -> [ParameterSetup a] Source #

equalExperiments :: (a, InputState a) -> (a, InputState a) -> Bool Source #

This function defines how to find experiments that can be resumed. Note that the experiments name and experiment info parameters are always comparison factors, that is, experiments with different names or info parameters are unequal. The default is always True.

default equalExperiments :: (a, InputState a) -> (a, InputState a) -> Bool Source #

serialisable :: a -> ExpM a (Serializable a) Source #

Function to convert to a serializable object. Can be used to convert the state to serialisable representation.

default serialisable :: a ~ Serializable a => a -> ExpM a (Serializable a) Source #

deserialisable :: Serializable a -> ExpM a a Source #

Function to convert from a serializable object. Can be used to convert the state from its serialisable representation.

default deserialisable :: a ~ Serializable a => Serializable a -> ExpM a a Source #

beforePreparationHook :: ExperimentNumber -> RepetitionNumber -> GenIO -> a -> ExpM a a Source #

Function to call on the state before the preparation. This function is only executed if the preparation phase exists (that is >0 preparation steps) and is started from period 0!

beforeWarmUpHook :: ExperimentNumber -> RepetitionNumber -> ReplicationNumber -> GenIO -> a -> ExpM a a Source #

Function to call on the state before the warm up phase. This function is only executed if a warm up phase exists (that is >0 warm-up steps) and is initialised, which happens on the first time it is started!

beforeEvaluationHook :: ExperimentNumber -> RepetitionNumber -> ReplicationNumber -> GenIO -> a -> ExpM a a Source #

Function to call on the state before the evaluation phase. This function is only executed if the evaluation phase exists (that is >0 evaluation steps) and is initialised which happens on the first time it is started!

afterPreparationHook :: a -> ExperimentNumber -> RepetitionNumber -> IO () Source #

Function to call after the preparation phase, e.g. it can be used to move files. This function is only executed if the preparation phase is updated. The first parameter is the input state and is only used for type checking.

afterWarmUpHook :: a -> ExperimentNumber -> RepetitionNumber -> ReplicationNumber -> IO () Source #

Function to call after the warmUp phase, e.g. it can be used to move files. This function is only executed if the warmUp phase is updated. The first parameter is the input state and is only used for type checking.

afterEvaluationHook :: a -> ExperimentNumber -> RepetitionNumber -> ReplicationNumber -> IO () Source #

Function to call after the evaluation phase, e.g. it can be used to move files. This function is only executed if the evaluation phase is updated. The first parameter is the input state before the evaluation and is only used for type checking.