aivika-2.0: A multi-paradigm simulation library

Stabilityexperimental
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Safe HaskellNone

Simulation.Aivika.Results

Contents

Description

Tested with: GHC 7.8.3

The module allows exporting the simulation results from the model.

Synopsis

Definitions Focused on Modeling

data Results Source

It contains the results of simulation.

Instances

Monoid Results 

type ResultTransform = Results -> ResultsSource

It transforms the results of simulation.

type ResultName = StringSource

A name used for indentifying the results when generating output.

class ResultProvider p whereSource

Represents a provider of the simulation results. It is usually something, or an array of something, or a list of such values which can be simulated to get data.

Methods

resultSource :: ResultName -> ResultDescription -> p -> ResultSourceSource

Return the source of simulation results by the specified name, description and provider.

resultSource' :: ResultName -> ResultId -> p -> ResultSourceSource

Return the source of simulation results by the specified name, identifier and provider.

Instances

results :: [ResultSource] -> ResultsSource

Prepare the simulation results.

expandResults :: ResultTransformSource

Return an expanded version of the simulation results expanding the properties as possible, which takes place for expanding statistics to show the count, average, deviation, minimum, maximum etc. as separate values.

resultSummary :: ResultTransformSource

Return a short version of the simulation results, i.e. their summary, expanding the main properties or excluding auxiliary properties if required.

resultByName :: ResultName -> ResultTransformSource

Take a result by its name.

resultByProperty :: ResultName -> ResultTransformSource

Take a result from the object with the specified property label, but it is more preferrable to refer to the property by its ResultId identifier with help of the resultById function.

resultById :: ResultId -> ResultTransformSource

Take a result from the object with the specified identifier. It can identify an item, object property, the object iself, vector or its elements.

resultByIndex :: Int -> ResultTransformSource

Take a result from the vector by the specified integer index.

resultBySubscript :: ResultName -> ResultTransformSource

Take a result from the vector by the specified string subscript.

class ResultComputing m whereSource

Represents a computation that can return the simulation data.

Methods

computeResultData :: m a -> ResultData aSource

Compute data with the results of simulation.

computeResultSignal :: m a -> ResultSignalSource

Return the signal triggered when data change if such a signal exists.

data ResultComputation a Source

Represents a computation that can return the simulation data.

Constructors

ResultComputation 

Fields

resultComputationData :: ResultData a

Return data from the computation.

resultComputationSignal :: ResultSignal

Return a signal from the computation.

data ResultListWithSubscript p Source

Represents a list with the specified subscript.

Constructors

ResultListWithSubscript [p] [String] 

data ResultArrayWithSubscript i p Source

Represents an array with the specified subscript.

Constructors

ResultArrayWithSubscript (Array i p) (Array i String) 

Instances

data ResultVectorWithSubscript p Source

Represents a vector with the specified subscript.

Constructors

ResultVectorWithSubscript (Vector p) (Vector String) 

Definitions Focused on Using the Library

data ResultExtract e Source

Defines a final result extract: its name, values and other data.

Constructors

ResultExtract 

Fields

resultExtractName :: ResultName

The result name.

resultExtractId :: ResultId

The result identifier.

resultExtractData :: Event e

The result values.

resultExtractSignal :: ResultSignal

Whether the result emits a signal.

extractIntResults :: Results -> [ResultExtract Int]Source

Extract the results as integer values, or raise a conversion error.

extractIntListResults :: Results -> [ResultExtract [Int]]Source

Extract the results as lists of integer values, or raise a conversion error.

extractIntStatsResults :: Results -> [ResultExtract (SamplingStats Int)]Source

Extract the results as statistics based on integer values, or raise a conversion error.

extractIntStatsEitherResults :: Results -> [ResultExtract (Either Int (SamplingStats Int))]Source

Extract the results as statistics based on integer values and optimised for fast aggregation, or raise a conversion error.

extractIntTimingStatsResults :: Results -> [ResultExtract (TimingStats Int)]Source

Extract the results as timing statistics based on integer values, or raise a conversion error.

extractDoubleResults :: Results -> [ResultExtract Double]Source

Extract the results as double floating point values, or raise a conversion error.

extractDoubleListResults :: Results -> [ResultExtract [Double]]Source

Extract the results as lists of double floating point values, or raise a conversion error.

extractDoubleStatsResults :: Results -> [ResultExtract (SamplingStats Double)]Source

Extract the results as statistics based on double floating point values, or raise a conversion error.

extractDoubleStatsEitherResults :: Results -> [ResultExtract (Either Double (SamplingStats Double))]Source

Extract the results as statistics based on double floating point values and optimised for fast aggregation, or raise a conversion error.

extractDoubleTimingStatsResults :: Results -> [ResultExtract (TimingStats Double)]Source

Extract the results as timing statistics based on double floating point values, or raise a conversion error.

extractStringResults :: Results -> [ResultExtract String]Source

Extract the results as string values, or raise a conversion error.

data ResultPredefinedSignals Source

It representes the predefined signals provided by every simulation model.

Constructors

ResultPredefinedSignals 

Fields

resultSignalInIntegTimes :: Signal Double

The signal triggered in the integration time points.

resultSignalInStartTime :: Signal Double

The signal triggered in the start time.

resultSignalInStopTime :: Signal Double

The signal triggered in the stop time.

newResultPredefinedSignals :: Simulation ResultPredefinedSignalsSource

Create the predefined signals provided by every simulation model.

resultSignal :: Results -> ResultSignalSource

Return a signal emitted by the specified results.

pureResultSignal :: ResultPredefinedSignals -> ResultSignal -> Signal ()Source

Return a pure signal as a result of combination of the predefined signals with the specified result signal usually provided by the sources.

The signal returned is triggered when the source signal is triggered. The pure signal is also triggered in the integration time points if the source signal is unknown or it was combined with any unknown signal.

Definitions Focused on Extending the Library

type ResultSourceMap = Map ResultName ResultSourceSource

It associates the result sources with their names.

data ResultSource Source

Encapsulates the result source.

Constructors

ResultItemSource ResultItem

The source consisting of a single item.

ResultObjectSource ResultObject

An object-like source.

ResultVectorSource ResultVector

A vector-like structure.

ResultSeparatorSource ResultSeparator

This is a separator text.

data ResultItem Source

The simulation results represented by a single item.

Constructors

forall a . ResultItemable a => ResultItem a 

class ResultItemable a whereSource

Represents a type class for actual representing the items.

Methods

resultItemName :: a -> ResultNameSource

The item name.

resultItemId :: a -> ResultIdSource

The item identifier.

resultItemSignal :: a -> ResultSignalSource

Whether the item emits a signal.

resultItemExpansion :: a -> ResultSourceSource

Return an expanded version of the item, for example, when the statistics item is exanded to an object having the corresponded properties for count, average, deviation, minimum, maximum and so on.

resultItemSummary :: a -> ResultSourceSource

Return usually a short version of the item, i.e. its summary, but values of some data types such as statistics can be implicitly expanded to an object with the corresponded properties.

resultItemToIntValue :: a -> ResultValue IntSource

Return integer numbers in time points.

resultItemToIntListValue :: a -> ResultValue [Int]Source

Return lists of integer numbers in time points.

resultItemToIntStatsValue :: a -> ResultValue (SamplingStats Int)Source

Return statistics based on integer numbers.

resultItemToIntTimingStatsValue :: a -> ResultValue (TimingStats Int)Source

Return timing statistics based on integer numbers.

resultItemToDoubleValue :: a -> ResultValue DoubleSource

Return double numbers in time points.

resultItemToDoubleListValue :: a -> ResultValue [Double]Source

Return lists of double numbers in time points.

resultItemToDoubleStatsValue :: a -> ResultValue (SamplingStats Double)Source

Return statistics based on double numbers.

resultItemToDoubleTimingStatsValue :: a -> ResultValue (TimingStats Double)Source

Return timing statistics based on integer numbers.

resultItemToStringValue :: a -> ResultValue StringSource

Return string representations in time points.

resultItemToIntStatsEitherValue :: ResultItemable a => a -> ResultValue (Either Int (SamplingStats Int))Source

Return a version optimised for fast aggregation of the statistics based on integer numbers.

resultItemToDoubleStatsEitherValue :: ResultItemable a => a -> ResultValue (Either Double (SamplingStats Double))Source

Return a version optimised for fast aggregation of the statistics based on double floating point numbers.

data ResultObject Source

The simulation results represented by an object having properties.

Constructors

ResultObject 

Fields

resultObjectName :: ResultName

The object name.

resultObjectId :: ResultId

The object identifier.

resultObjectTypeId :: ResultId

The object type identifier.

resultObjectProperties :: [ResultProperty]

The object properties.

resultObjectSignal :: ResultSignal

A combined signal if present.

resultObjectSummary :: ResultSource

A short version of the object, i.e. its summary.

data ResultProperty Source

The object property containing the simulation results.

Constructors

ResultProperty 

Fields

resultPropertyLabel :: ResultName

The property short label.

resultPropertyId :: ResultId

The property identifier.

resultPropertySource :: ResultSource

The simulation results supplied by the property.

data ResultVector Source

The simulation results represented by a vector.

Constructors

ResultVector 

Fields

resultVectorName :: ResultName

The vector name.

resultVectorId :: ResultId

The vector identifier.

resultVectorItems :: Array Int ResultSource

The results supplied by the vector items.

resultVectorSubscript :: Array Int ResultName

The subscript used as a suffix to create item names.

resultVectorSignal :: ResultSignal

A combined signal if present.

resultVectorSummary :: ResultSource

A short version of the vector, i.e. summary.

memoResultVectorSignal :: ResultVector -> ResultVectorSource

Calculate the result vector signal and memoize it in a new vector.

memoResultVectorSummary :: ResultVector -> ResultVectorSource

Calculate the result vector summary and memoize it in a new vector.

data ResultSeparator Source

It separates the simulation results when printing.

Constructors

ResultSeparator 

Fields

resultSeparatorText :: String

The separator text.

data ResultValue e Source

A parameterised value that actually represents a generalised result item that have no parametric type.

Constructors

ResultValue 

Fields

resultValueName :: ResultName

The value name.

resultValueId :: ResultId

The value identifier.

resultValueData :: ResultData e

Simulation data supplied by the value.

resultValueSignal :: ResultSignal

Whether the value emits a signal when changing simulation data.

voidResultValue :: ResultValue a -> ResultValue bSource

Return a new value with the discarded simulation results.

data ResultContainer e Source

A container of the simulation results such as queue, server or array.

Constructors

ResultContainer 

Fields

resultContainerName :: ResultName

The container name.

resultContainerId :: ResultId

The container identifier.

resultContainerData :: e

The container data.

resultContainerSignal :: ResultSignal

Whether the container emits a signal when changing simulation data.

Instances

Functor ResultContainer 

resultContainerPropertySourceSource

Arguments

:: ResultItemable (ResultValue b) 
=> ResultContainer a

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> ResultData b)

get the specified data from the container

-> (a -> ResultSignal)

get the data signal from the container

-> ResultSource 

Create a new property source by the specified container.

resultContainerConstPropertySource

Arguments

:: ResultItemable (ResultValue b) 
=> ResultContainer a

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> b)

get the specified data from the container

-> ResultProperty 

Create a constant property by the specified container.

resultContainerIntegPropertySource

Arguments

:: ResultItemable (ResultValue b) 
=> ResultContainer a

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> Event b)

get the specified data from the container

-> ResultProperty 

Create by the specified container a property that changes in the integration time points, or it is supposed to be such one.

resultContainerPropertySource

Arguments

:: ResultItemable (ResultValue b) 
=> ResultContainer a

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> Event b)

get the specified data from the container

-> (a -> Signal ())

get a signal triggered when changing data.

-> ResultProperty 

Create a property by the specified container.

resultContainerMapPropertySource

Arguments

:: ResultItemable (ResultValue b) 
=> ResultContainer (ResultData a)

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> b)

recompute the specified data

-> ResultProperty 

Create by the specified container a mapped property which is recomputed each time again and again.

resultValueToContainer :: ResultValue a -> ResultContainer (ResultData a)Source

Convert the result value to a container with the specified object identifier.

resultContainerToValue :: ResultContainer (ResultData a) -> ResultValue aSource

Convert the result container to a value.

type ResultData e = Maybe (Event e)Source

Represents the very simulation results.

data ResultSignal Source

Whether an object containing the results emits a signal notifying about change of data.

Constructors

EmptyResultSignal

There is no signal at all.

UnknownResultSignal

The signal is unknown, but the entity probably changes.

ResultSignal (Signal ())

When the signal is precisely specified.

ResultSignalMix (Signal ())

When the specified signal was combined with unknown signal.

Instances

Monoid ResultSignal 

maybeResultSignal :: Maybe (Signal ()) -> ResultSignalSource

Construct a new result signal by the specified optional pure signal.

textResultSource :: String -> ResultSourceSource

Return an arbitrary text as a separator source.

timeResultSource :: ResultSourceSource

Return the source of the modeling time.

resultSourceToIntValues :: ResultSource -> [ResultValue Int]Source

Represent the result source as integer numbers.

resultSourceToIntListValues :: ResultSource -> [ResultValue [Int]]Source

Represent the result source as lists of integer numbers.

resultSourceToIntStatsValues :: ResultSource -> [ResultValue (SamplingStats Int)]Source

Represent the result source as statistics based on integer numbers.

resultSourceToIntStatsEitherValues :: ResultSource -> [ResultValue (Either Int (SamplingStats Int))]Source

Represent the result source as statistics based on integer numbers and optimised for fast aggregation.

resultSourceToIntTimingStatsValues :: ResultSource -> [ResultValue (TimingStats Int)]Source

Represent the result source as timing statistics based on integer numbers.

resultSourceToDoubleValues :: ResultSource -> [ResultValue Double]Source

Represent the result source as double floating point numbers.

resultSourceToDoubleListValues :: ResultSource -> [ResultValue [Double]]Source

Represent the result source as lists of double floating point numbers.

resultSourceToDoubleStatsValues :: ResultSource -> [ResultValue (SamplingStats Double)]Source

Represent the result source as statistics based on double floating point numbers.

resultSourceToDoubleStatsEitherValues :: ResultSource -> [ResultValue (Either Double (SamplingStats Double))]Source

Represent the result source as statistics based on double floating point numbers and optimised for fast aggregation.

resultSourceToDoubleTimingStatsValues :: ResultSource -> [ResultValue (TimingStats Double)]Source

Represent the result source as timing statistics based on double floating point numbers.

resultSourceToStringValues :: ResultSource -> [ResultValue String]Source

Represent the result source as string values.

resultSourceMap :: Results -> ResultSourceMapSource

The sources of simulation results as a map of associated names.

resultSourceList :: Results -> [ResultSource]Source

The sources of simulation results as an ordered list.

resultsToIntValues :: Results -> [ResultValue Int]Source

Represent the results as integer numbers.

resultsToIntListValues :: Results -> [ResultValue [Int]]Source

Represent the results as lists of integer numbers.

resultsToIntStatsValues :: Results -> [ResultValue (SamplingStats Int)]Source

Represent the results as statistics based on integer numbers.

resultsToIntStatsEitherValues :: Results -> [ResultValue (Either Int (SamplingStats Int))]Source

Represent the results as statistics based on integer numbers and optimised for fast aggregation.

resultsToIntTimingStatsValues :: Results -> [ResultValue (TimingStats Int)]Source

Represent the results as timing statistics based on integer numbers.

resultsToDoubleValues :: Results -> [ResultValue Double]Source

Represent the results as double floating point numbers.

resultsToDoubleListValues :: Results -> [ResultValue [Double]]Source

Represent the results as lists of double floating point numbers.

resultsToDoubleStatsValues :: Results -> [ResultValue (SamplingStats Double)]Source

Represent the results as statistics based on double floating point numbers.

resultsToDoubleStatsEitherValues :: Results -> [ResultValue (Either Double (SamplingStats Double))]Source

Represent the results as statistics based on double floating point numbers and optimised for fast aggregation.

resultsToDoubleTimingStatsValues :: Results -> [ResultValue (TimingStats Double)]Source

Represent the results as timing statistics based on double floating point numbers.

resultsToStringValues :: Results -> [ResultValue String]Source

Represent the results as string values.

composeResults :: (ResultSource -> [ResultSource]) -> ResultTransformSource

Compose the results using the specified transformation function.

computeResultValueSource

Arguments

:: ResultComputing m 
=> ResultName

the result name

-> ResultId

the result identifier

-> m a

the result computation

-> ResultValue a 

Return a new result value by the specified name, identifier and computation.