laborantin-hs-0.1.4.0: an experiment management framework

Safe HaskellNone

Laborantin.Types

Synopsis

Documentation

data ScenarioDescription m Source

A Scenario description carries all information to run an experiment.

Instances

data ParameterDescription Source

A ParameterDescription description carries information for a single parameter.

Constructors

PDesc 

Fields

pName :: Text
 
pDesc :: Text
 
pValues :: [ParameterValue]
 

data ParameterValue Source

Two parameter values type should be enough for command-line demands: text and numbers.

However, we provide two other constructors (Array and Range) for the ParameterDescriptions in the DSL.

Executions should use text and numbers only.

type ParameterSpace = Map Text ParameterDescriptionSource

A ParameterSpace maps parameter names to their descriptions.

type ParameterSet = Map Text ParameterValueSource

A ParameterSet (slightly different from a ParameterSpace) is a mapping between parameter names and a single ParameterValue.

You can see a ParameterSet as a datapoint within a (multidimensional) ParameterSpace.

Thus, to keep things clearer, we recommend that executions use only text and numbers as ParameterValues.

paramSets :: ParameterSpace -> [ParameterSet]Source

Returns an exhaustive list of ParameterSet (i.e., all data points) to cover a (multidimensional) ParameterSpace.

Basically a Cartesian product.

mergeParamSpaces :: ParameterSpace -> ParameterSpace -> ParameterSpaceSource

Merges two ParameterSpace by extending all dimensions.

updateParam :: ParameterSpace -> Text -> [ParameterValue] -> ParameterSpaceSource

Updates a single dimension of the ParameterSpace to be the list of ParameterValue s in 3rd parameter.

expandValue :: ParameterValue -> [ParameterValue]Source

Expands a ParameterValue to a list of ParameterValues. Mainly flattens ranges.

data Result m Source

Backends must generate results that are easy to operate. They represent files with readwriteappend operations as execution steps.

Note that Backend might not implement all three of read, write, append operations.

Constructors

Result 

Fields

pPath :: FilePath
 
pRead :: Step m Text
 
pAppend :: Text -> Step m ()
 
pWrite :: Text -> Step m ()
 

data Backend m Source

A Backend captures all functions that an object must provide to run Laborantin experiments.

Such functions give ways to prepare, run, analyze, and finalize executions. As well as provide support for logging info, storing, finding, and deleting prior results.

We prefer such a design over a typeclass to simplify overall design and unclutter type definitions everywhere.

Constructors

Backend 

Fields

bName :: Text
 
bPrepareExecution :: ScenarioDescription m -> ParameterSet -> m (Execution m, Finalizer m)
 
bFinalizeExecution :: Execution m -> Finalizer m -> m ()
 
bSetup :: Execution m -> Step m ()
 
bRun :: Execution m -> Step m ()
 
bTeardown :: Execution m -> Step m ()
 
bAnalyze :: Execution m -> Step m ()
 
bRecover :: ExecutionError -> Execution m -> Step m ()
 
bResult :: Execution m -> FilePath -> Step m (Result m)
 
bLoad :: [ScenarioDescription m] -> TExpr Bool -> m [Execution m]
 
bLogger :: Execution m -> Step m (LogHandler m)
 
bRemove :: Execution m -> m ()
 

data Execution m Source

An Execution represents an ongoing or past experiment result.

Instances

data StoredExecution Source

An StoredExecution is a stripped-down version of an Execution.

As it represents an experiment stored on disk, it does not need to carry the ScenarioDescription object (otherwise it would become harder to create instances such as FromJSON for Executions).

type Finalizer m = Execution m -> m ()Source

newtype LogHandler m Source

Constructors

LogHandler 

Fields

lLog :: Text -> Step m ()
 

type Step m a = ErrorT ExecutionError (StateT DynEnv (ReaderT (Backend m, Execution m) m)) aSource

A step is a stateful operation for a Scenario phase. It carries a modifiable DynEnv between hooks and handle ExecutionErrors. In addition, you can read (but not modify) the Backend and the Execution.

newtype Action m Source

An Action wraps a monadic computation inside a step.

Constructors

Action 

Fields

unAction :: Step m ()
 

Instances

type DynEnv = Map Text DynamicSource

DynEnv is a map between Text keys and Dynamic values.

data Dependency m Source

A Dependency is a lose but flexible way of expressing dependencies for experiments.

Dependencies can check whether they are fullfilled, and try to solve. The main goal for the design of Dependency dCheck and dSolve hooks is to let a Dependency run experiments and add them as ancestors *before* starting any Step. Types may slightly vary in the future.

Dependencies can do anything that a ScenarioDescription allows (hence they are parametrized with the same monad as the ScenarioDescription owning a Dependency). However, Dependency check and Dependency resolution do not live in a Step m . That is they do not have access to, and cannot modify, the DynEnv. Thus, this limits the possibility to read execution parameters from within the dCheck and dSolve.

To compensate for this limitation, the dCheck hook accepts the Execution as parameter and the dSolve hook accepts both the Execution and the Backend as parameter, and get a chance to return a modified Execution object.

Constructors

Dep 

Fields

dName :: Text
 
dDesc :: Text
 
dCheck :: Execution m -> m Bool
 
dSolve :: (Execution m, Backend m) -> m (Execution m)
 

Instances