{-# LANGUAGE FlexibleInstances #-}

-- |
-- Module     : Simulation.Aivika.Results.Transform
-- Copyright  : Copyright (c) 2009-2017, David Sorokin <david.sorokin@gmail.com>
-- License    : BSD3
-- Maintainer : David Sorokin <david.sorokin@gmail.com>
-- Stability  : experimental
-- Tested with: GHC 8.0.1
--
-- The module defines useful result transformations that can
-- be used in simulation experiments.
--
module Simulation.Aivika.Results.Transform
       (-- * Basic Class Type
        ResultTransformer(..),
        -- * Sampling Statistics
        SamplingStats(..),
        samplingStatsCount,
        samplingStatsMin,
        samplingStatsMax,
        samplingStatsMean,
        samplingStatsMean2,
        samplingStatsVariance,
        samplingStatsDeviation,
        -- * Time-dependent Statistics
        TimingStats(..),
        timingStatsCount,
        timingStatsMin,
        timingStatsMax,
        timingStatsMean,
        timingStatsVariance,
        timingStatsDeviation,
        timingStatsMinTime,
        timingStatsMaxTime,
        timingStatsStartTime,
        timingStatsLastTime,
        timingStatsSum,
        timingStatsSum2,
        -- * Sampling-based Counter
        SamplingCounter(..),
        samplingCounterValue,
        samplingCounterStats,
        -- * Time-dependent Counter
        TimingCounter(..),
        timingCounterValue,
        timingCounterStats,
        -- * Queue
        Queue(..),
        enqueueStrategy,
        enqueueStoringStrategy,
        dequeueStrategy,
        queueNull,
        queueFull,
        queueMaxCount,
        queueCount,
        queueCountStats,
        enqueueCount,
        enqueueLostCount,
        enqueueStoreCount,
        dequeueCount,
        dequeueExtractCount,
        queueLoadFactor,
        enqueueRate,
        enqueueStoreRate,
        dequeueRate,
        dequeueExtractRate,
        queueWaitTime,
        queueTotalWaitTime,
        enqueueWaitTime,
        dequeueWaitTime,
        queueRate,
        -- * Arrival Timer
        ArrivalTimer(..),
        arrivalProcessingTime,
        -- * Server
        Server(..),
        serverInitState,
        serverState,
        serverTotalInputWaitTime,
        serverTotalProcessingTime,
        serverTotalOutputWaitTime,
        serverTotalPreemptionTime,
        serverInputWaitTime,
        serverProcessingTime,
        serverOutputWaitTime,
        serverPreemptionTime,
        serverInputWaitFactor,
        serverProcessingFactor,
        serverOutputWaitFactor,
        serverPreemptionFactor,
        -- * Activity
        Activity(..),
        activityInitState,
        activityState,
        activityTotalUtilisationTime,
        activityTotalIdleTime,
        activityTotalPreemptionTime,
        activityUtilisationTime,
        activityIdleTime,
        activityPreemptionTime,
        activityUtilisationFactor,
        activityIdleFactor,
        activityPreemptionFactor,
        -- * Resource
        Resource(..),
        resourceCount,
        resourceCountStats,
        resourceUtilisationCount,
        resourceUtilisationCountStats,
        resourceQueueCount,
        resourceQueueCountStats,
        resourceTotalWaitTime,
        resourceWaitTime,
        -- * Operation
        Operation(..),
        operationTotalUtilisationTime,
        operationTotalPreemptionTime,
        operationUtilisationTime,
        operationPreemptionTime,
        operationUtilisationFactor,
        operationPreemptionFactor) where

import Control.Arrow

import Simulation.Aivika.Results
import Simulation.Aivika.Results.Locale

-- | Something that can transform the results.
class ResultTransformer a where

  -- | Return the result transform.
  tr :: a -> ResultTransform

-- | Represents a statistics based upon observations.
newtype SamplingStats = SamplingStats ResultTransform

instance ResultTransformer SamplingStats where
  tr :: SamplingStats -> ResultTransform
tr (SamplingStats ResultTransform
a) = ResultTransform
a

-- | The total number of samples.
samplingStatsCount :: SamplingStats -> ResultTransform
samplingStatsCount :: SamplingStats -> ResultTransform
samplingStatsCount (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsCountId

-- | The minimum value among the samples.
samplingStatsMin :: SamplingStats -> ResultTransform
samplingStatsMin :: SamplingStats -> ResultTransform
samplingStatsMin (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsMinId

-- | The maximum value among the samples.
samplingStatsMax :: SamplingStats -> ResultTransform
samplingStatsMax :: SamplingStats -> ResultTransform
samplingStatsMax (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsMaxId
  
-- | The average value.
samplingStatsMean :: SamplingStats -> ResultTransform
samplingStatsMean :: SamplingStats -> ResultTransform
samplingStatsMean (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsMeanId

-- | The average square value.
samplingStatsMean2 :: SamplingStats -> ResultTransform
samplingStatsMean2 :: SamplingStats -> ResultTransform
samplingStatsMean2 (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsMean2Id

-- | Return tha variance.
samplingStatsVariance :: SamplingStats -> ResultTransform
samplingStatsVariance :: SamplingStats -> ResultTransform
samplingStatsVariance (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsVarianceId

-- | Return the deviation.
samplingStatsDeviation :: SamplingStats -> ResultTransform
samplingStatsDeviation :: SamplingStats -> ResultTransform
samplingStatsDeviation (SamplingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingStatsDeviationId

-- | A counter for which the statistics is collected too.
newtype SamplingCounter = SamplingCounter ResultTransform

instance ResultTransformer SamplingCounter where
  tr :: SamplingCounter -> ResultTransform
tr (SamplingCounter ResultTransform
a) = ResultTransform
a

-- | The counter value.
samplingCounterValue :: SamplingCounter -> ResultTransform
samplingCounterValue :: SamplingCounter -> ResultTransform
samplingCounterValue (SamplingCounter ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingCounterValueId

-- | The counter statistics.
samplingCounterStats :: SamplingCounter -> SamplingStats
samplingCounterStats :: SamplingCounter -> SamplingStats
samplingCounterStats (SamplingCounter ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
SamplingCounterStatsId)

-- | The time-dependent statistics.
newtype TimingStats = TimingStats ResultTransform

instance ResultTransformer TimingStats where
  tr :: TimingStats -> ResultTransform
tr (TimingStats ResultTransform
a) = ResultTransform
a

-- | Return the number of samples.
timingStatsCount :: TimingStats -> ResultTransform
timingStatsCount :: TimingStats -> ResultTransform
timingStatsCount (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsCountId

-- | Return the minimum value.
timingStatsMin :: TimingStats -> ResultTransform
timingStatsMin :: TimingStats -> ResultTransform
timingStatsMin (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsMinId

-- | Return the maximum value.
timingStatsMax :: TimingStats -> ResultTransform
timingStatsMax :: TimingStats -> ResultTransform
timingStatsMax (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsMaxId

-- | Return the average value.
timingStatsMean :: TimingStats -> ResultTransform
timingStatsMean :: TimingStats -> ResultTransform
timingStatsMean (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsMeanId

-- | Return the variance.
timingStatsVariance :: TimingStats -> ResultTransform
timingStatsVariance :: TimingStats -> ResultTransform
timingStatsVariance (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsVarianceId

-- | Return the deviation.
timingStatsDeviation :: TimingStats -> ResultTransform
timingStatsDeviation :: TimingStats -> ResultTransform
timingStatsDeviation (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsDeviationId

-- | Return the time at which the minimum is attained.
timingStatsMinTime :: TimingStats -> ResultTransform
timingStatsMinTime :: TimingStats -> ResultTransform
timingStatsMinTime (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsMinTimeId

-- | Return the time at which the maximum is attained.
timingStatsMaxTime :: TimingStats -> ResultTransform
timingStatsMaxTime :: TimingStats -> ResultTransform
timingStatsMaxTime (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsMaxTimeId

-- | Return the start time of sampling.
timingStatsStartTime :: TimingStats -> ResultTransform
timingStatsStartTime :: TimingStats -> ResultTransform
timingStatsStartTime (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsStartTimeId

-- | Return the last time of sampling.
timingStatsLastTime :: TimingStats -> ResultTransform
timingStatsLastTime :: TimingStats -> ResultTransform
timingStatsLastTime (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsLastTimeId

-- | Return the sum of values.
timingStatsSum :: TimingStats -> ResultTransform
timingStatsSum :: TimingStats -> ResultTransform
timingStatsSum (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsSumId

-- | Return the sum of square values.
timingStatsSum2 :: TimingStats -> ResultTransform
timingStatsSum2 :: TimingStats -> ResultTransform
timingStatsSum2 (TimingStats ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultTransform
expandResults ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingStatsSum2Id

-- | A time-dependent counter that collects the statistics too.
newtype TimingCounter = TimingCounter ResultTransform

instance ResultTransformer TimingCounter where
  tr :: TimingCounter -> ResultTransform
tr (TimingCounter ResultTransform
a) = ResultTransform
a

-- | The counter value.
timingCounterValue :: TimingCounter -> ResultTransform
timingCounterValue :: TimingCounter -> ResultTransform
timingCounterValue (TimingCounter ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingCounterValueId

-- | The counter statistics.
timingCounterStats :: TimingCounter -> TimingStats
timingCounterStats :: TimingCounter -> TimingStats
timingCounterStats (TimingCounter ResultTransform
a) =
  ResultTransform -> TimingStats
TimingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
TimingCounterStatsId)

-- | Represents either finite or infinite queue.
newtype Queue = Queue ResultTransform

instance ResultTransformer Queue where
  tr :: Queue -> ResultTransform
tr (Queue ResultTransform
a) = ResultTransform
a

-- | The strategy applied to the enqueueing (input) processes when the finite queue is full.
enqueueStrategy :: Queue -> ResultTransform
enqueueStrategy :: Queue -> ResultTransform
enqueueStrategy (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueStrategyId

-- | The strategy applied when storing (in memory) items in the queue.
enqueueStoringStrategy :: Queue -> ResultTransform
enqueueStoringStrategy :: Queue -> ResultTransform
enqueueStoringStrategy (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueStoringStrategyId

-- | The strategy applied to the dequeueing (output) processes when the queue is empty.
dequeueStrategy :: Queue -> ResultTransform
dequeueStrategy :: Queue -> ResultTransform
dequeueStrategy (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
DequeueStrategyId

-- | Test whether the queue is empty.
queueNull :: Queue -> ResultTransform
queueNull :: Queue -> ResultTransform
queueNull (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueNullId

-- | Test whether the finite queue is full.
queueFull :: Queue -> ResultTransform
queueFull :: Queue -> ResultTransform
queueFull (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueFullId

-- | The finite queue capacity.
queueMaxCount :: Queue -> ResultTransform
queueMaxCount :: Queue -> ResultTransform
queueMaxCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueMaxCountId

-- | Return the current queue size.
queueCount :: Queue -> ResultTransform
queueCount :: Queue -> ResultTransform
queueCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueCountId

-- | Return the queue size statistics.
queueCountStats :: Queue -> TimingStats
queueCountStats :: Queue -> TimingStats
queueCountStats (Queue ResultTransform
a) =
  ResultTransform -> TimingStats
TimingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueCountStatsId)

-- | Return the total number of input items that were enqueued in the finite queue.
enqueueCount :: Queue -> ResultTransform
enqueueCount :: Queue -> ResultTransform
enqueueCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueCountId

-- | Return the number of lost items for the finite queue.
enqueueLostCount :: Queue -> ResultTransform
enqueueLostCount :: Queue -> ResultTransform
enqueueLostCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueLostCountId

-- | Return the total number of input items that were stored.
enqueueStoreCount :: Queue -> ResultTransform
enqueueStoreCount :: Queue -> ResultTransform
enqueueStoreCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueStoreCountId

-- | Return the total number of requests for dequeueing the items, not taking
-- into account the failed attempts to dequeue immediately without suspension.
dequeueCount :: Queue -> ResultTransform
dequeueCount :: Queue -> ResultTransform
dequeueCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
DequeueCountId

-- | Return the total number of output items that were actually dequeued.
dequeueExtractCount :: Queue -> ResultTransform
dequeueExtractCount :: Queue -> ResultTransform
dequeueExtractCount (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
DequeueExtractCountId

-- | Return the load factor: the finite queue size divided by its capacity.
queueLoadFactor :: Queue -> ResultTransform
queueLoadFactor :: Queue -> ResultTransform
queueLoadFactor (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueLoadFactorId

-- | Return the rate of the input items that were enqueued in the finite queue:
-- how many items per time.
enqueueRate :: Queue -> ResultTransform
enqueueRate :: Queue -> ResultTransform
enqueueRate (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueRateId

-- | Return the rate of the items that were stored: how many items per time.
enqueueStoreRate :: Queue -> ResultTransform
enqueueStoreRate :: Queue -> ResultTransform
enqueueStoreRate (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueStoreRateId

-- | Return the rate of the requests for dequeueing the items: how many
-- requests per time. It does not include the failed attempts to dequeue
-- immediately without suspension.
dequeueRate :: Queue -> ResultTransform
dequeueRate :: Queue -> ResultTransform
dequeueRate (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
DequeueRateId

-- | Return the rate of the output items that were dequeued: how many items per time.
dequeueExtractRate :: Queue -> ResultTransform
dequeueExtractRate :: Queue -> ResultTransform
dequeueExtractRate (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
DequeueExtractRateId

-- | Return the wait time from the time at which the item was stored in
-- the queue to the time at which it was dequeued.
queueWaitTime :: Queue -> SamplingStats
queueWaitTime :: Queue -> SamplingStats
queueWaitTime (Queue ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueWaitTimeId)

-- | Return the total wait time for the finite queue from the time at which
-- the enqueueing operation was initiated to the time at which the item was dequeued.
queueTotalWaitTime :: Queue -> SamplingStats
queueTotalWaitTime :: Queue -> SamplingStats
queueTotalWaitTime (Queue ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueTotalWaitTimeId)

-- | Return the wait time from the time at which the item was stored in
-- the queue to the time at which it was dequeued.
enqueueWaitTime :: Queue -> SamplingStats
enqueueWaitTime :: Queue -> SamplingStats
enqueueWaitTime (Queue ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
EnqueueWaitTimeId)

-- | Return the dequeue wait time from the time at which the item was requested
-- for dequeueing to the time at which it was actually dequeued.
dequeueWaitTime :: Queue -> SamplingStats
dequeueWaitTime :: Queue -> SamplingStats
dequeueWaitTime (Queue ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
DequeueWaitTimeId)

-- | Return a long-term average queue rate calculated as the average queue size
-- divided by the average wait time.
queueRate :: Queue -> ResultTransform
queueRate :: Queue -> ResultTransform
queueRate (Queue ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
QueueRateId

-- | Accumulates the statistics about that how long the arrived events are processed.
newtype ArrivalTimer = ArrivalTimer ResultTransform

instance ResultTransformer ArrivalTimer where
  tr :: ArrivalTimer -> ResultTransform
tr (ArrivalTimer ResultTransform
a) = ResultTransform
a

-- | Return the statistics about that how long the arrived events were processed.
arrivalProcessingTime :: ArrivalTimer -> SamplingStats
arrivalProcessingTime :: ArrivalTimer -> SamplingStats
arrivalProcessingTime (ArrivalTimer ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ArrivalProcessingTimeId)

-- | It models the server that prodives a service.
newtype Server = Server ResultTransform

instance ResultTransformer Server where
  tr :: Server -> ResultTransform
tr (Server ResultTransform
a) = ResultTransform
a

-- | The initial state of the server.
serverInitState :: Server -> ResultTransform
serverInitState :: Server -> ResultTransform
serverInitState (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerInitStateId

-- | Return the current state of the server.
serverState :: Server -> ResultTransform
serverState :: Server -> ResultTransform
serverState (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerStateId

-- | Return the counted total time when the server was locked while
-- awaiting the input.
serverTotalInputWaitTime :: Server -> ResultTransform
serverTotalInputWaitTime :: Server -> ResultTransform
serverTotalInputWaitTime (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerTotalInputWaitTimeId

-- | Return the counted total time spent by the server while
-- processing the tasks.
serverTotalProcessingTime :: Server -> ResultTransform
serverTotalProcessingTime :: Server -> ResultTransform
serverTotalProcessingTime (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerTotalProcessingTimeId

-- | Return the counted total time when the server was locked while
-- trying to deliver the output.
serverTotalOutputWaitTime :: Server -> ResultTransform
serverTotalOutputWaitTime :: Server -> ResultTransform
serverTotalOutputWaitTime (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerTotalOutputWaitTimeId

-- | Return the counted total time spent by the server while it was
-- preempted waiting for the further proceeding.
serverTotalPreemptionTime :: Server -> ResultTransform
serverTotalPreemptionTime :: Server -> ResultTransform
serverTotalPreemptionTime (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerTotalPreemptionTimeId

-- | Return the statistics of the time when the server was locked
-- while awaiting the input.
serverInputWaitTime :: Server -> SamplingStats
serverInputWaitTime :: Server -> SamplingStats
serverInputWaitTime (Server ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerInputWaitTimeId)

-- | Return the statistics of the time spent by the server while
-- processing the tasks.
serverProcessingTime :: Server -> SamplingStats
serverProcessingTime :: Server -> SamplingStats
serverProcessingTime (Server ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerProcessingTimeId)

-- | Return the statistics of the time when the server was locked
-- while trying to deliver the output.
serverOutputWaitTime :: Server -> SamplingStats
serverOutputWaitTime :: Server -> SamplingStats
serverOutputWaitTime (Server ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerOutputWaitTimeId)

-- | Return the statistics of the time spent by the server while
-- it was preempted waiting for the further proceeding.
serverPreemptionTime :: Server -> SamplingStats
serverPreemptionTime :: Server -> SamplingStats
serverPreemptionTime (Server ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerPreemptionTimeId)

-- | It returns the factor changing from 0 to 1, which estimates
-- how often the server was awaiting for the next input task.
serverInputWaitFactor :: Server -> ResultTransform
serverInputWaitFactor :: Server -> ResultTransform
serverInputWaitFactor (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerInputWaitFactorId

-- | It returns the factor changing from 0 to 1, which estimates
-- how often the server was busy with direct processing its tasks.
serverProcessingFactor :: Server -> ResultTransform
serverProcessingFactor :: Server -> ResultTransform
serverProcessingFactor (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerProcessingFactorId

-- | It returns the factor changing from 0 to 1, which estimates
-- how often the server was locked trying to deliver the output
-- after the task is finished.
serverOutputWaitFactor :: Server -> ResultTransform
serverOutputWaitFactor :: Server -> ResultTransform
serverOutputWaitFactor (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerOutputWaitFactorId

-- | It returns the factor changing from 0 to 1, which estimates
-- how often the server was preempted waiting for the further proceeding.
serverPreemptionFactor :: Server -> ResultTransform
serverPreemptionFactor :: Server -> ResultTransform
serverPreemptionFactor (Server ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ServerPreemptionFactorId

-- | It models an activity that can be utilised.
newtype Activity = Activity ResultTransform

instance ResultTransformer Activity where
  tr :: Activity -> ResultTransform
tr (Activity ResultTransform
a) = ResultTransform
a

-- | The initial state of the activity.
activityInitState :: Activity -> ResultTransform
activityInitState :: Activity -> ResultTransform
activityInitState (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityInitStateId

-- | Return the current state of the activity.
activityState :: Activity -> ResultTransform
activityState :: Activity -> ResultTransform
activityState (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityStateId

-- | Return the counted total time when the activity was utilised.
activityTotalUtilisationTime :: Activity -> ResultTransform
activityTotalUtilisationTime :: Activity -> ResultTransform
activityTotalUtilisationTime (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityTotalUtilisationTimeId

-- | Return the counted total time when the activity was idle.
activityTotalIdleTime :: Activity -> ResultTransform
activityTotalIdleTime :: Activity -> ResultTransform
activityTotalIdleTime (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityTotalIdleTimeId

-- | Return the counted total time when the activity was preemted
-- waiting for the further proceeding.
activityTotalPreemptionTime :: Activity -> ResultTransform
activityTotalPreemptionTime :: Activity -> ResultTransform
activityTotalPreemptionTime (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityTotalPreemptionTimeId

-- | Return the statistics for the time when the activity was utilised.
activityUtilisationTime :: Activity -> SamplingStats
activityUtilisationTime :: Activity -> SamplingStats
activityUtilisationTime (Activity ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityUtilisationTimeId)

-- | Return the statistics for the time when the activity was idle.
activityIdleTime :: Activity -> SamplingStats
activityIdleTime :: Activity -> SamplingStats
activityIdleTime (Activity ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityIdleTimeId)

-- | Return the statistics for the time when the activity was preempted
-- waiting for the further proceeding.
activityPreemptionTime :: Activity -> SamplingStats
activityPreemptionTime :: Activity -> SamplingStats
activityPreemptionTime (Activity ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityPreemptionTimeId)

-- | It returns the factor changing from 0 to 1, which estimates how often
-- the activity was utilised.
activityUtilisationFactor :: Activity -> ResultTransform
activityUtilisationFactor :: Activity -> ResultTransform
activityUtilisationFactor (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityUtilisationFactorId

-- | It returns the factor changing from 0 to 1, which estimates how often
-- the activity was idle.
activityIdleFactor :: Activity -> ResultTransform
activityIdleFactor :: Activity -> ResultTransform
activityIdleFactor (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityIdleFactorId

-- | It returns the factor changing from 0 to 1, which estimates how often
-- the activity was preempted waiting for the further proceeding.
activityPreemptionFactor :: Activity -> ResultTransform
activityPreemptionFactor :: Activity -> ResultTransform
activityPreemptionFactor (Activity ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ActivityPreemptionFactorId

-- | The resource which can be acquired and then released.
newtype Resource = Resource ResultTransform

instance ResultTransformer Resource where
  tr :: Resource -> ResultTransform
tr (Resource ResultTransform
a) = ResultTransform
a

-- | Return the current available count of the resource.
resourceCount :: Resource -> ResultTransform
resourceCount :: Resource -> ResultTransform
resourceCount (Resource ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceCountId

-- | Return the statistics for the available count of the resource.
resourceCountStats :: Resource -> TimingStats
resourceCountStats :: Resource -> TimingStats
resourceCountStats (Resource ResultTransform
a) =
  ResultTransform -> TimingStats
TimingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceCountStatsId)

-- | Return the current utilisation count of the resource.
resourceUtilisationCount :: Resource -> ResultTransform
resourceUtilisationCount :: Resource -> ResultTransform
resourceUtilisationCount (Resource ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceUtilisationCountId

-- | Return the statistics for the utilisation count of the resource.
resourceUtilisationCountStats :: Resource -> TimingStats
resourceUtilisationCountStats :: Resource -> TimingStats
resourceUtilisationCountStats (Resource ResultTransform
a) =
  ResultTransform -> TimingStats
TimingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceUtilisationCountStatsId)

-- | Return the current queue length of the resource.
resourceQueueCount :: Resource -> ResultTransform
resourceQueueCount :: Resource -> ResultTransform
resourceQueueCount (Resource ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceQueueCountId

-- | Return the statistics for the queue length of the resource.
resourceQueueCountStats :: Resource -> TimingStats
resourceQueueCountStats :: Resource -> TimingStats
resourceQueueCountStats (Resource ResultTransform
a) =
  ResultTransform -> TimingStats
TimingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceQueueCountStatsId)

-- | Return the total wait time of the resource.
resourceTotalWaitTime :: Resource -> ResultTransform
resourceTotalWaitTime :: Resource -> ResultTransform
resourceTotalWaitTime (Resource ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceTotalWaitTimeId

-- | Return the statistics for the wait time of the resource.
resourceWaitTime :: Resource -> SamplingStats
resourceWaitTime :: Resource -> SamplingStats
resourceWaitTime (Resource ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
ResourceWaitTimeId)

-- | It models an opreation which actvity can be utilised.
newtype Operation = Operation ResultTransform

instance ResultTransformer Operation where
  tr :: Operation -> ResultTransform
tr (Operation ResultTransform
a) = ResultTransform
a

-- | Return the counted total time when the operation activity was utilised.
operationTotalUtilisationTime :: Operation -> ResultTransform
operationTotalUtilisationTime :: Operation -> ResultTransform
operationTotalUtilisationTime (Operation ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
OperationTotalUtilisationTimeId

-- | Return the counted total time when the operation activity was preemted
-- waiting for the further proceeding.
operationTotalPreemptionTime :: Operation -> ResultTransform
operationTotalPreemptionTime :: Operation -> ResultTransform
operationTotalPreemptionTime (Operation ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
OperationTotalPreemptionTimeId

-- | Return the statistics for the time when the operation activity was utilised.
operationUtilisationTime :: Operation -> SamplingStats
operationUtilisationTime :: Operation -> SamplingStats
operationUtilisationTime (Operation ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
OperationUtilisationTimeId)

-- | Return the statistics for the time when the operation activity was preempted
-- waiting for the further proceeding.
operationPreemptionTime :: Operation -> SamplingStats
operationPreemptionTime :: Operation -> SamplingStats
operationPreemptionTime (Operation ResultTransform
a) =
  ResultTransform -> SamplingStats
SamplingStats (ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
OperationPreemptionTimeId)

-- | It returns the factor changing from 0 to 1, which estimates how often
-- the operation activity was utilised.
operationUtilisationFactor :: Operation -> ResultTransform
operationUtilisationFactor :: Operation -> ResultTransform
operationUtilisationFactor (Operation ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
OperationUtilisationFactorId

-- | It returns the factor changing from 0 to 1, which estimates how often
-- the operation activity was preempted waiting for the further proceeding.
operationPreemptionFactor :: Operation -> ResultTransform
operationPreemptionFactor :: Operation -> ResultTransform
operationPreemptionFactor (Operation ResultTransform
a) =
  ResultTransform
a ResultTransform -> ResultTransform -> ResultTransform
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> ResultId -> ResultTransform
resultById ResultId
OperationPreemptionFactorId