Copyright | Copyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Tested with: GHC 8.0.1
This module defines the resource which can be acquired and
then released by the discontinuous process Process
.
The resource can be either limited by the upper bound
(run-time check), or it can have no upper bound. The latter
is useful for modeling the infinite queue, for example.
Synopsis
- type FCFSResource m = Resource m FCFS
- type LCFSResource m = Resource m LCFS
- type SIROResource m = Resource m SIRO
- type PriorityResource m = Resource m StaticPriorities
- data Resource m s
- newFCFSResource :: MonadDES m => Int -> Event m (FCFSResource m)
- newFCFSResourceWithMaxCount :: MonadDES m => Int -> Maybe Int -> Event m (FCFSResource m)
- newLCFSResource :: MonadDES m => Int -> Event m (LCFSResource m)
- newLCFSResourceWithMaxCount :: MonadDES m => Int -> Maybe Int -> Event m (LCFSResource m)
- newSIROResource :: (MonadDES m, QueueStrategy m SIRO) => Int -> Event m (SIROResource m)
- newSIROResourceWithMaxCount :: (MonadDES m, QueueStrategy m SIRO) => Int -> Maybe Int -> Event m (SIROResource m)
- newPriorityResource :: (MonadDES m, QueueStrategy m StaticPriorities) => Int -> Event m (PriorityResource m)
- newPriorityResourceWithMaxCount :: (MonadDES m, QueueStrategy m StaticPriorities) => Int -> Maybe Int -> Event m (PriorityResource m)
- newResource :: (MonadDES m, QueueStrategy m s) => s -> Int -> Event m (Resource m s)
- newResourceWithMaxCount :: (MonadDES m, QueueStrategy m s) => s -> Int -> Maybe Int -> Event m (Resource m s)
- resourceStrategy :: Resource m s -> s
- resourceMaxCount :: Resource m s -> Maybe Int
- resourceCount :: MonadDES m => Resource m s -> Event m Int
- resourceCountStats :: MonadDES m => Resource m s -> Event m (TimingStats Int)
- resourceUtilisationCount :: MonadDES m => Resource m s -> Event m Int
- resourceUtilisationCountStats :: MonadDES m => Resource m s -> Event m (TimingStats Int)
- resourceQueueCount :: MonadDES m => Resource m s -> Event m Int
- resourceQueueCountStats :: MonadDES m => Resource m s -> Event m (TimingStats Int)
- resourceTotalWaitTime :: MonadDES m => Resource m s -> Event m Double
- resourceWaitTime :: MonadDES m => Resource m s -> Event m (SamplingStats Double)
- requestResource :: (MonadDES m, EnqueueStrategy m s) => Resource m s -> Process m ()
- requestResourceWithPriority :: (MonadDES m, PriorityQueueStrategy m s p) => Resource m s -> p -> Process m ()
- tryRequestResourceWithinEvent :: MonadDES m => Resource m s -> Event m Bool
- releaseResource :: (MonadDES m, DequeueStrategy m s) => Resource m s -> Process m ()
- releaseResourceWithinEvent :: (MonadDES m, DequeueStrategy m s) => Resource m s -> Event m ()
- usingResource :: (MonadDES m, EnqueueStrategy m s) => Resource m s -> Process m a -> Process m a
- usingResourceWithPriority :: (MonadDES m, PriorityQueueStrategy m s p) => Resource m s -> p -> Process m a -> Process m a
- incResourceCount :: (MonadDES m, DequeueStrategy m s) => Resource m s -> Int -> Event m ()
- decResourceCount :: (MonadDES m, EnqueueStrategy m s) => Resource m s -> Int -> Process m ()
- resetResource :: MonadDES m => Resource m s -> Event m ()
- resourceCountChanged :: MonadDES m => Resource m s -> Signal m Int
- resourceCountChanged_ :: MonadDES m => Resource m s -> Signal m ()
- resourceUtilisationCountChanged :: MonadDES m => Resource m s -> Signal m Int
- resourceUtilisationCountChanged_ :: MonadDES m => Resource m s -> Signal m ()
- resourceQueueCountChanged :: MonadDES m => Resource m s -> Signal m Int
- resourceQueueCountChanged_ :: MonadDES m => Resource m s -> Signal m ()
- resourceWaitTimeChanged :: MonadDES m => Resource m s -> Signal m (SamplingStats Double)
- resourceWaitTimeChanged_ :: MonadDES m => Resource m s -> Signal m ()
- resourceChanged_ :: MonadDES m => Resource m s -> Signal m ()
Resource Types
type FCFSResource m = Resource m FCFS Source #
The ordinary FCFS (First Come - First Serviced) resource.
type LCFSResource m = Resource m LCFS Source #
The ordinary LCFS (Last Come - First Serviced) resource.
type SIROResource m = Resource m SIRO Source #
The SIRO (Serviced in Random Order) resource.
type PriorityResource m = Resource m StaticPriorities Source #
The resource with static priorities.
Represents the resource with strategy s
applied for queuing the requests.
Instances
(MonadDES m, Show s, ResultItemable (ResultValue s)) => ResultProvider (Resource m s) m Source # | |
Defined in Simulation.Aivika.Trans.Results resultSource :: ResultName -> ResultDescription -> Resource m s -> ResultSource m Source # resultSource3 :: ResultName -> ResultDescription -> ResultDescription -> Resource m s -> ResultSource m Source # resultSource' :: ResultName -> [ResultName] -> ResultId -> [ResultId] -> Resource m s -> ResultSource m Source # |
Creating Resource
:: MonadDES m | |
=> Int | the initial count (and maximal count too) of the resource |
-> Event m (FCFSResource m) |
Create a new FCFS resource with the specified initial count which value becomes the upper bound as well.
newFCFSResourceWithMaxCount Source #
:: MonadDES m | |
=> Int | the initial count of the resource |
-> Maybe Int | the maximum count of the resource, which can be indefinite |
-> Event m (FCFSResource m) |
Create a new FCFS resource with the specified initial and maximum counts,
where Nothing
means that the resource has no upper bound.
:: MonadDES m | |
=> Int | the initial count (and maximal count too) of the resource |
-> Event m (LCFSResource m) |
Create a new LCFS resource with the specified initial count which value becomes the upper bound as well.
newLCFSResourceWithMaxCount Source #
:: MonadDES m | |
=> Int | the initial count of the resource |
-> Maybe Int | the maximum count of the resource, which can be indefinite |
-> Event m (LCFSResource m) |
Create a new LCFS resource with the specified initial and maximum counts,
where Nothing
means that the resource has no upper bound.
:: (MonadDES m, QueueStrategy m SIRO) | |
=> Int | the initial count (and maximal count too) of the resource |
-> Event m (SIROResource m) |
Create a new SIRO resource with the specified initial count which value becomes the upper bound as well.
newSIROResourceWithMaxCount Source #
:: (MonadDES m, QueueStrategy m SIRO) | |
=> Int | the initial count of the resource |
-> Maybe Int | the maximum count of the resource, which can be indefinite |
-> Event m (SIROResource m) |
Create a new SIRO resource with the specified initial and maximum counts,
where Nothing
means that the resource has no upper bound.
:: (MonadDES m, QueueStrategy m StaticPriorities) | |
=> Int | the initial count (and maximal count too) of the resource |
-> Event m (PriorityResource m) |
Create a new priority resource with the specified initial count which value becomes the upper bound as well.
newPriorityResourceWithMaxCount Source #
:: (MonadDES m, QueueStrategy m StaticPriorities) | |
=> Int | the initial count of the resource |
-> Maybe Int | the maximum count of the resource, which can be indefinite |
-> Event m (PriorityResource m) |
Create a new priority resource with the specified initial and maximum counts,
where Nothing
means that the resource has no upper bound.
:: (MonadDES m, QueueStrategy m s) | |
=> s | the strategy for managing the queuing requests |
-> Int | the initial count (and maximal count too) of the resource |
-> Event m (Resource m s) |
Create a new resource with the specified queue strategy and initial count. The last value becomes the upper bound as well.
newResourceWithMaxCount Source #
:: (MonadDES m, QueueStrategy m s) | |
=> s | the strategy for managing the queuing requests |
-> Int | the initial count of the resource |
-> Maybe Int | the maximum count of the resource, which can be indefinite |
-> Event m (Resource m s) |
Create a new resource with the specified queue strategy, initial and maximum counts,
where Nothing
means that the resource has no upper bound.
Resource Properties
resourceStrategy :: Resource m s -> s Source #
Return the strategy applied for queuing the requests.
resourceMaxCount :: Resource m s -> Maybe Int Source #
Return the maximum count of the resource, where Nothing
means that the resource has no upper bound.
resourceCount :: MonadDES m => Resource m s -> Event m Int Source #
Return the current available count of the resource.
resourceCountStats :: MonadDES m => Resource m s -> Event m (TimingStats Int) Source #
Return the statistics for the available count of the resource.
resourceUtilisationCount :: MonadDES m => Resource m s -> Event m Int Source #
Return the current utilisation count of the resource.
resourceUtilisationCountStats :: MonadDES m => Resource m s -> Event m (TimingStats Int) Source #
Return the statistics for the utilisation count of the resource.
resourceQueueCount :: MonadDES m => Resource m s -> Event m Int Source #
Return the current queue length of the resource.
resourceQueueCountStats :: MonadDES m => Resource m s -> Event m (TimingStats Int) Source #
Return the statistics for the queue length of the resource.
resourceTotalWaitTime :: MonadDES m => Resource m s -> Event m Double Source #
Return the total wait time of the resource.
resourceWaitTime :: MonadDES m => Resource m s -> Event m (SamplingStats Double) Source #
Return the statistics for the wait time of the resource.
Requesting for and Releasing Resource
:: (MonadDES m, EnqueueStrategy m s) | |
=> Resource m s | the requested resource |
-> Process m () |
Request for the resource decreasing its count in case of success, otherwise suspending the discontinuous process until some other process releases the resource.
requestResourceWithPriority Source #
:: (MonadDES m, PriorityQueueStrategy m s p) | |
=> Resource m s | the requested resource |
-> p | the priority |
-> Process m () |
Request with the priority for the resource decreasing its count in case of success, otherwise suspending the discontinuous process until some other process releases the resource.
:: (MonadDES m, DequeueStrategy m s) | |
=> Resource m s | the resource to release |
-> Process m () |
Release the resource increasing its count and resuming one of the previously suspended processes as possible.
releaseResourceWithinEvent Source #
:: (MonadDES m, DequeueStrategy m s) | |
=> Resource m s | the resource to release |
-> Event m () |
Release the resource increasing its count and resuming one of the previously suspended processes as possible.
:: (MonadDES m, EnqueueStrategy m s) | |
=> Resource m s | the resource we are going to request for and then release in the end |
-> Process m a | the action we are going to apply having the resource |
-> Process m a | the result of the action |
Acquire the resource, perform some action and safely release the resource
in the end, even if the IOException
was raised within the action.
usingResourceWithPriority Source #
:: (MonadDES m, PriorityQueueStrategy m s p) | |
=> Resource m s | the resource we are going to request for and then release in the end |
-> p | the priority |
-> Process m a | the action we are going to apply having the resource |
-> Process m a | the result of the action |
Acquire the resource with the specified priority, perform some action and
safely release the resource in the end, even if the IOException
was raised
within the action.
Altering Resource
:: (MonadDES m, DequeueStrategy m s) | |
=> Resource m s | the resource |
-> Int | the increment for the resource count |
-> Event m () |
Increase the count of available resource by the specified number, invoking the awaiting processes as needed.
:: (MonadDES m, EnqueueStrategy m s) | |
=> Resource m s | the resource |
-> Int | the decrement for the resource count |
-> Process m () |
Decrease the count of available resource by the specified number, waiting for the processes capturing the resource as needed.
Statistics Reset
Signals
resourceCountChanged :: MonadDES m => Resource m s -> Signal m Int Source #
Signal triggered when the resourceCount
property changes.
resourceCountChanged_ :: MonadDES m => Resource m s -> Signal m () Source #
Signal triggered when the resourceCount
property changes.
resourceUtilisationCountChanged :: MonadDES m => Resource m s -> Signal m Int Source #
Signal triggered when the resourceUtilisationCount
property changes.
resourceUtilisationCountChanged_ :: MonadDES m => Resource m s -> Signal m () Source #
Signal triggered when the resourceUtilisationCount
property changes.
resourceQueueCountChanged :: MonadDES m => Resource m s -> Signal m Int Source #
Signal triggered when the resourceQueueCount
property changes.
resourceQueueCountChanged_ :: MonadDES m => Resource m s -> Signal m () Source #
Signal triggered when the resourceQueueCount
property changes.
resourceWaitTimeChanged :: MonadDES m => Resource m s -> Signal m (SamplingStats Double) Source #
Signal triggered when the resourceTotalWaitTime
and resourceWaitTime
properties change.
resourceWaitTimeChanged_ :: MonadDES m => Resource m s -> Signal m () Source #
Signal triggered when the resourceTotalWaitTime
and resourceWaitTime
properties change.