module Simulation.Aivika.GPSS.Results.Transform where
import Control.Category
import Simulation.Aivika
import qualified Simulation.Aivika.Results.Transform as T
import qualified Simulation.Aivika.GPSS.Queue as Q
import qualified Simulation.Aivika.GPSS.Facility as F
import qualified Simulation.Aivika.GPSS.Storage as S
import Simulation.Aivika.GPSS.Results
import Simulation.Aivika.GPSS.Results.Locale
newtype Queue = Queue ResultTransform
instance T.ResultTransformer Queue where
tr :: Queue -> ResultTransform
tr (Queue ResultTransform
a) = ResultTransform
a
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
queueContent :: Queue -> ResultTransform
queueContent :: Queue -> ResultTransform
queueContent (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
queueContentId
queueContentStats :: Queue -> T.TimingStats
queueContentStats :: Queue -> TimingStats
queueContentStats (Queue ResultTransform
a) =
ResultTransform -> TimingStats
T.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
queueContentStatsId)
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
enqueueZeroEntryCount :: Queue -> ResultTransform
enqueueZeroEntryCount :: Queue -> ResultTransform
enqueueZeroEntryCount (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
enqueueZeroEntryCountId
queueWaitTime :: Queue -> T.SamplingStats
queueWaitTime :: Queue -> SamplingStats
queueWaitTime (Queue ResultTransform
a) =
ResultTransform -> SamplingStats
T.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)
queueNonZeroEntryWaitTime :: Queue -> T.SamplingStats
queueNonZeroEntryWaitTime :: Queue -> SamplingStats
queueNonZeroEntryWaitTime (Queue ResultTransform
a) =
ResultTransform -> SamplingStats
T.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
queueNonZeroEntryWaitTimeId)
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
newtype Facility = Facility ResultTransform
instance T.ResultTransformer Facility where
tr :: Facility -> ResultTransform
tr (Facility ResultTransform
a) = ResultTransform
a
facilityCount :: Facility -> ResultTransform
facilityCount :: Facility -> ResultTransform
facilityCount (Facility 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
facilityCountId
facilityCountStats :: Facility -> T.TimingStats
facilityCountStats :: Facility -> TimingStats
facilityCountStats (Facility ResultTransform
a) =
ResultTransform -> TimingStats
T.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
facilityCountStatsId)
facilityCaptureCount :: Facility -> ResultTransform
facilityCaptureCount :: Facility -> ResultTransform
facilityCaptureCount (Facility 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
facilityCaptureCountId
facilityUtilisationCount :: Facility -> ResultTransform
facilityUtilisationCount :: Facility -> ResultTransform
facilityUtilisationCount (Facility 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
facilityUtilisationCountId
facilityUtilisationCountStats :: Facility -> T.TimingStats
facilityUtilisationCountStats :: Facility -> TimingStats
facilityUtilisationCountStats (Facility ResultTransform
a) =
ResultTransform -> TimingStats
T.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
facilityUtilisationCountStatsId)
facilityQueueCount :: Facility -> ResultTransform
facilityQueueCount :: Facility -> ResultTransform
facilityQueueCount (Facility 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
facilityQueueCountId
facilityQueueCountStats :: Facility -> T.TimingStats
facilityQueueCountStats :: Facility -> TimingStats
facilityQueueCountStats (Facility ResultTransform
a) =
ResultTransform -> TimingStats
T.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
facilityQueueCountStatsId)
facilityTotalWaitTime :: Facility -> ResultTransform
facilityTotalWaitTime :: Facility -> ResultTransform
facilityTotalWaitTime (Facility 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
facilityTotalWaitTimeId
facilityWaitTime :: Facility -> T.SamplingStats
facilityWaitTime :: Facility -> SamplingStats
facilityWaitTime (Facility ResultTransform
a) =
ResultTransform -> SamplingStats
T.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
facilityWaitTimeId)
facilityTotalHoldingTime :: Facility -> ResultTransform
facilityTotalHoldingTime :: Facility -> ResultTransform
facilityTotalHoldingTime (Facility 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
facilityTotalHoldingTimeId
facilityHoldingTime :: Facility -> T.SamplingStats
facilityHoldingTime :: Facility -> SamplingStats
facilityHoldingTime (Facility ResultTransform
a) =
ResultTransform -> SamplingStats
T.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
facilityHoldingTimeId)
facilityInterrupted :: Facility -> ResultTransform
facilityInterrupted :: Facility -> ResultTransform
facilityInterrupted (Facility 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
facilityInterruptedId
newtype Storage = Storage ResultTransform
instance T.ResultTransformer Storage where
tr :: Storage -> ResultTransform
tr (Storage ResultTransform
a) = ResultTransform
a
storageCapacity :: Storage -> ResultTransform
storageCapacity :: Storage -> ResultTransform
storageCapacity (Storage 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
storageCapacityId
storageEmpty :: Storage -> ResultTransform
storageEmpty :: Storage -> ResultTransform
storageEmpty (Storage 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
storageEmptyId
storageFull :: Storage -> ResultTransform
storageFull :: Storage -> ResultTransform
storageFull (Storage 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
storageFullId
storageContent :: Storage -> ResultTransform
storageContent :: Storage -> ResultTransform
storageContent (Storage 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
storageContentId
storageContentStats :: Storage -> T.TimingStats
storageContentStats :: Storage -> TimingStats
storageContentStats (Storage ResultTransform
a) =
ResultTransform -> TimingStats
T.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
storageContentStatsId)
storageUseCount :: Storage -> ResultTransform
storageUseCount :: Storage -> ResultTransform
storageUseCount (Storage 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
storageUseCountId
storageUsedContent :: Storage -> ResultTransform
storageUsedContent :: Storage -> ResultTransform
storageUsedContent (Storage 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
storageUsedContentId
storageUtilisationCount :: Storage -> ResultTransform
storageUtilisationCount :: Storage -> ResultTransform
storageUtilisationCount (Storage 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
storageUtilisationCountId
storageUtilisationCountStats :: Storage -> T.TimingStats
storageUtilisationCountStats :: Storage -> TimingStats
storageUtilisationCountStats (Storage ResultTransform
a) =
ResultTransform -> TimingStats
T.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
storageUtilisationCountStatsId)
storageQueueCount :: Storage -> ResultTransform
storageQueueCount :: Storage -> ResultTransform
storageQueueCount (Storage 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
storageQueueCountId
storageQueueCountStats :: Storage -> T.TimingStats
storageQueueCountStats :: Storage -> TimingStats
storageQueueCountStats (Storage ResultTransform
a) =
ResultTransform -> TimingStats
T.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
storageQueueCountStatsId)
storageTotalWaitTime :: Storage -> ResultTransform
storageTotalWaitTime :: Storage -> ResultTransform
storageTotalWaitTime (Storage 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
storageTotalWaitTimeId
storageWaitTime :: Storage -> T.SamplingStats
storageWaitTime :: Storage -> SamplingStats
storageWaitTime (Storage ResultTransform
a) =
ResultTransform -> SamplingStats
T.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
storageWaitTimeId)
storageAverageHoldingTime :: Storage -> ResultTransform
storageAverageHoldingTime :: Storage -> ResultTransform
storageAverageHoldingTime (Storage 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
storageAverageHoldingTimeId