aivika-transformers-4.3.5: Transformers for the Aivika simulation library

CopyrightCopyright (c) 2009-2015, David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Simulation.Aivika.Trans.Results

Contents

Description

Tested with: GHC 7.10.1

The module allows exporting the simulation results from the model.

Synopsis

Definitions Focused on Modeling

data Results m Source

It contains the results of simulation.

Instances

type ResultTransform m = Results m -> Results m Source

It transforms the results of simulation.

type ResultName = String Source

A name used for indentifying the results when generating output.

class MonadDES m => ResultProvider p m | p -> m where Source

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.

Minimal complete definition

resultSource'

Methods

resultSource :: ResultName -> ResultDescription -> p -> ResultSource m Source

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

resultSource' :: ResultName -> ResultId -> p -> ResultSource m Source

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

Instances

ResultProvider p m => ResultProvider [p] m Source 
ResultProvider p m => ResultProvider (Vector p) m Source 
MonadResource m => ResultProvider (Resource m) m Source 
MonadDES m => ResultProvider (ArrivalTimer m) m Source 
ResultProvider p m => ResultProvider (ResultVectorWithSubscript p) m Source 
ResultProvider p m => ResultProvider (ResultListWithSubscript p) m Source 
ResultComputing t m => ResultProvider (t m (Vector Int)) m Source 
ResultComputing t m => ResultProvider (t m (Vector Double)) m Source 
(Ix i, Show i, ResultComputing t m) => ResultProvider (t m (Array i Int)) m Source 
(Ix i, Show i, ResultComputing t m) => ResultProvider (t m (Array i Double)) m Source 
ResultComputing t m => ResultProvider (t m String) m Source 
ResultComputing t m => ResultProvider (t m (TimingCounter Int)) m Source 
ResultComputing t m => ResultProvider (t m (SamplingCounter Int)) m Source 
ResultComputing t m => ResultProvider (t m (TimingStats Int)) m Source 
ResultComputing t m => ResultProvider (t m (SamplingStats Int)) m Source 
ResultComputing t m => ResultProvider (t m [Int]) m Source 
ResultComputing t m => ResultProvider (t m Int) m Source 
ResultComputing t m => ResultProvider (t m (TimingCounter Double)) m Source 
ResultComputing t m => ResultProvider (t m (SamplingCounter Double)) m Source 
ResultComputing t m => ResultProvider (t m (TimingStats Double)) m Source 
ResultComputing t m => ResultProvider (t m (SamplingStats Double)) m Source 
ResultComputing t m => ResultProvider (t m [Double]) m Source 
ResultComputing t m => ResultProvider (t m Double) m Source 
(Show i, Ix i, ResultProvider p m) => ResultProvider (Array i p) m Source 
(MonadDES m, Show s, ResultItemable (ResultValue s)) => ResultProvider (Resource m s) m Source 
(Show i, Ix i, ResultProvider p m) => ResultProvider (ResultArrayWithSubscript i p) m Source 
MonadDES m => ResultProvider (Operation m a b) m Source 
(MonadDES m, Show sm, Show so, ResultItemable (ResultValue sm), ResultItemable (ResultValue so)) => ResultProvider (Queue m sm so a) m Source 
(MonadDES m, Show s, ResultItemable (ResultValue s)) => ResultProvider (Server m s a b) m Source 
(MonadDES m, Show s, ResultItemable (ResultValue s)) => ResultProvider (Activity m s a b) m Source 
(MonadDES m, Show si, Show sm, Show so, ResultItemable (ResultValue si), ResultItemable (ResultValue sm), ResultItemable (ResultValue so)) => ResultProvider (Queue m si sm so a) m Source 

results :: [ResultSource m] -> Results m Source

Prepare the simulation results.

expandResults :: MonadDES m => ResultTransform m Source

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 :: MonadDES m => ResultTransform m Source

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

resultByName :: ResultName -> ResultTransform m Source

Take a result by its name.

resultByProperty :: ResultName -> ResultTransform m Source

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 -> ResultTransform m Source

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 -> ResultTransform m Source

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

resultBySubscript :: ResultName -> ResultTransform m Source

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

class MonadDES m => ResultComputing t m where Source

Represents a computation that can return the simulation data.

Methods

computeResultData :: t m a -> ResultData a m Source

Compute data with the results of simulation.

computeResultSignal :: t m a -> ResultSignal m Source

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

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) 

data ResultVectorWithSubscript p Source

Represents a vector with the specified subscript.

Definitions Focused on Using the Library

resultsToIntValues :: MonadDES m => Results m -> [ResultValue Int m] Source

Represent the results as integer numbers.

resultsToIntListValues :: MonadDES m => Results m -> [ResultValue [Int] m] Source

Represent the results as lists of integer numbers.

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

Represent the results as statistics based on integer numbers.

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

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

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

Represent the results as timing statistics based on integer numbers.

resultsToDoubleValues :: MonadDES m => Results m -> [ResultValue Double m] Source

Represent the results as double floating point numbers.

resultsToDoubleListValues :: MonadDES m => Results m -> [ResultValue [Double] m] Source

Represent the results as lists of double floating point numbers.

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

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

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

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

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

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

resultsToStringValues :: MonadDES m => Results m -> [ResultValue String m] Source

Represent the results as string values.

data ResultPredefinedSignals m Source

It representes the predefined signals provided by every simulation model.

Constructors

ResultPredefinedSignals 

Fields

resultSignalInIntegTimes :: Signal m Double

The signal triggered in the integration time points.

resultSignalInStartTime :: Signal m Double

The signal triggered in the start time.

resultSignalInStopTime :: Signal m Double

The signal triggered in the stop time.

newResultPredefinedSignals :: MonadDES m => Simulation m (ResultPredefinedSignals m) Source

Create the predefined signals provided by every simulation model.

resultSignal :: MonadDES m => Results m -> ResultSignal m Source

Return a signal emitted by the specified results.

pureResultSignal :: MonadDES m => ResultPredefinedSignals m -> ResultSignal m -> Signal m () 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 m = Map ResultName (ResultSource m) Source

It associates the result sources with their names.

data ResultSource m Source

Encapsulates the result source.

Constructors

ResultItemSource (ResultItem m)

The source consisting of a single item.

ResultObjectSource (ResultObject m)

An object-like source.

ResultVectorSource (ResultVector m)

A vector-like structure.

ResultSeparatorSource ResultSeparator

This is a separator text.

data ResultItem m Source

The simulation results represented by a single item.

Constructors

forall a . ResultItemable a => ResultItem (a m) 

class ResultItemable a where Source

Represents a type class for actual representing the items.

Methods

resultItemName :: a m -> ResultName Source

The item name.

resultItemId :: a m -> ResultId Source

The item identifier.

resultItemSignal :: MonadDES m => a m -> ResultSignal m Source

Whether the item emits a signal.

resultItemExpansion :: MonadDES m => a m -> ResultSource m Source

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 :: MonadDES m => a m -> ResultSource m Source

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.

resultItemAsIntValue :: MonadDES m => a m -> Maybe (ResultValue Int m) Source

Try to return integer numbers in time points.

resultItemAsIntListValue :: MonadDES m => a m -> Maybe (ResultValue [Int] m) Source

Try to return lists of integer numbers in time points.

resultItemAsIntStatsValue :: MonadDES m => a m -> Maybe (ResultValue (SamplingStats Int) m) Source

Try to return statistics based on integer numbers.

resultItemAsIntTimingStatsValue :: MonadDES m => a m -> Maybe (ResultValue (TimingStats Int) m) Source

Try to return timing statistics based on integer numbers.

resultItemAsDoubleValue :: MonadDES m => a m -> Maybe (ResultValue Double m) Source

Try to return double numbers in time points.

resultItemAsDoubleListValue :: MonadDES m => a m -> Maybe (ResultValue [Double] m) Source

Try to return lists of double numbers in time points.

resultItemAsDoubleStatsValue :: MonadDES m => a m -> Maybe (ResultValue (SamplingStats Double) m) Source

Try to return statistics based on double numbers.

resultItemAsDoubleTimingStatsValue :: MonadDES m => a m -> Maybe (ResultValue (TimingStats Double) m) Source

Try to return timing statistics based on integer numbers.

resultItemAsStringValue :: MonadDES m => a m -> Maybe (ResultValue String m) Source

Try to return string representations in time points.

resultItemAsIntStatsEitherValue :: (MonadDES m, ResultItemable a) => a m -> Maybe (ResultValue (Either Int (SamplingStats Int)) m) Source

Try to return a version optimised for fast aggregation of the statistics based on integer numbers.

resultItemAsDoubleStatsEitherValue :: (MonadDES m, ResultItemable a) => a m -> Maybe (ResultValue (Either Double (SamplingStats Double)) m) Source

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

resultItemToIntValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue Int m Source

Return integer numbers in time points.

resultItemToIntListValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue [Int] m Source

Return lists of integer numbers in time points.

resultItemToIntStatsValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue (SamplingStats Int) m Source

Return statistics based on integer numbers.

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

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

resultItemToIntTimingStatsValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue (TimingStats Int) m Source

Return timing statistics based on integer numbers.

resultItemToDoubleValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue Double m Source

Return double numbers in time points.

resultItemToDoubleListValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue [Double] m Source

Return lists of double numbers in time points.

resultItemToDoubleStatsValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue (SamplingStats Double) m Source

Return statistics based on double numbers.

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

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

resultItemToDoubleTimingStatsValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue (TimingStats Double) m Source

Return timing statistics based on integer numbers.

resultItemToStringValue :: (MonadDES m, ResultItemable a) => a m -> ResultValue String m Source

Return string representations in time points.

data ResultObject m 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 m]

The object properties.

resultObjectSignal :: ResultSignal m

A combined signal if present.

resultObjectSummary :: ResultSource m

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

data ResultProperty m Source

The object property containing the simulation results.

Constructors

ResultProperty 

Fields

resultPropertyLabel :: ResultName

The property short label.

resultPropertyId :: ResultId

The property identifier.

resultPropertySource :: ResultSource m

The simulation results supplied by the property.

data ResultVector m 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 m)

The results supplied by the vector items.

resultVectorSubscript :: Array Int ResultName

The subscript used as a suffix to create item names.

resultVectorSignal :: ResultSignal m

A combined signal if present.

resultVectorSummary :: ResultSource m

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

memoResultVectorSignal :: MonadDES m => ResultVector m -> ResultVector m Source

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

memoResultVectorSummary :: MonadDES m => ResultVector m -> ResultVector m Source

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 ResultContainer e m 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 m

Whether the container emits a signal when changing simulation data.

resultContainerPropertySource Source

Arguments

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

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> ResultData b m)

get the specified data from the container

-> (a -> ResultSignal m)

get the data signal from the container

-> ResultSource m 

Create a new property source by the specified container.

resultContainerConstProperty Source

Arguments

:: (MonadDES m, ResultItemable (ResultValue b)) 
=> ResultContainer a m

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> b)

get the specified data from the container

-> ResultProperty m 

Create a constant property by the specified container.

resultContainerIntegProperty Source

Arguments

:: (MonadDES m, ResultItemable (ResultValue b)) 
=> ResultContainer a m

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> Event m b)

get the specified data from the container

-> ResultProperty m 

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

resultContainerProperty Source

Arguments

:: (MonadDES m, ResultItemable (ResultValue b)) 
=> ResultContainer a m

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> Event m b)

get the specified data from the container

-> (a -> Signal m ())

get a signal triggered when changing data.

-> ResultProperty m 

Create a property by the specified container.

resultContainerMapProperty Source

Arguments

:: (MonadDES m, ResultItemable (ResultValue b)) 
=> ResultContainer (ResultData a m) m

the container

-> ResultName

the property label

-> ResultId

the property identifier

-> (a -> b)

recompute the specified data

-> ResultProperty m 

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

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

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

resultContainerToValue :: ResultContainer (ResultData a m) m -> ResultValue a m Source

Convert the result container to a value.

type ResultData e m = Event m e Source

Represents the very simulation results.

data ResultSignal m 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 m ())

When the signal is precisely specified.

ResultSignalMix (Signal m ())

When the specified signal was combined with unknown signal.

Instances

maybeResultSignal :: Maybe (Signal m ()) -> ResultSignal m Source

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

textResultSource :: String -> ResultSource m Source

Return an arbitrary text as a separator source.

timeResultSource :: MonadDES m => ResultSource m Source

Return the source of the modeling time.

resultSourceToIntValues :: MonadDES m => ResultSource m -> [ResultValue Int m] Source

Represent the result source as integer numbers.

resultSourceToIntListValues :: MonadDES m => ResultSource m -> [ResultValue [Int] m] Source

Represent the result source as lists of integer numbers.

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

Represent the result source as statistics based on integer numbers.

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

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

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

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

resultSourceToDoubleValues :: MonadDES m => ResultSource m -> [ResultValue Double m] Source

Represent the result source as double floating point numbers.

resultSourceToDoubleListValues :: MonadDES m => ResultSource m -> [ResultValue [Double] m] Source

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

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

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

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

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

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

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

resultSourceToStringValues :: MonadDES m => ResultSource m -> [ResultValue String m] Source

Represent the result source as string values.

resultSourceMap :: Results m -> ResultSourceMap m Source

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

resultSourceList :: Results m -> [ResultSource m] Source

The sources of simulation results as an ordered list.

composeResults :: (ResultSource m -> [ResultSource m]) -> ResultTransform m Source

Compose the results using the specified transformation function.

computeResultValue Source

Arguments

:: ResultComputing t m 
=> ResultName

the result name

-> ResultId

the result identifier

-> t m a

the result computation

-> ResultValue a m 

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