-- |
-- Module     : Simulation.Aivika.Queue.Infinite
-- 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
--
-- This module defines an infinite queue that can use the specified strategies.
--
module Simulation.Aivika.Queue.Infinite
       (-- * Queue Types
        FCFSQueue,
        LCFSQueue,
        SIROQueue,
        PriorityQueue,
        Queue,
        -- * Creating Queue
        newFCFSQueue,
        newLCFSQueue,
        newSIROQueue,
        newPriorityQueue,
        newQueue,
        -- * Queue Properties and Activities
        enqueueStoringStrategy,
        dequeueStrategy,
        queueNull,
        queueCount,
        queueCountStats,
        enqueueStoreCount,
        dequeueCount,
        dequeueExtractCount,
        enqueueStoreRate,
        dequeueRate,
        dequeueExtractRate,
        queueWaitTime,
        dequeueWaitTime,
        queueRate,
        -- * Dequeuing and Enqueuing
        dequeue,
        dequeueWithOutputPriority,
        tryDequeue,
        enqueue,
        enqueueWithStoringPriority,
        queueDelete,
        queueDelete_,
        queueDeleteBy,
        queueDeleteBy_,
        queueContains,
        queueContainsBy,
        clearQueue,
        -- * Statistics Reset
        resetQueue,
        -- * Summary
        queueSummary,
        -- * Derived Signals for Properties
        queueNullChanged,
        queueNullChanged_,
        queueCountChanged,
        queueCountChanged_,
        enqueueStoreCountChanged,
        enqueueStoreCountChanged_,
        dequeueCountChanged,
        dequeueCountChanged_,
        dequeueExtractCountChanged,
        dequeueExtractCountChanged_,
        queueWaitTimeChanged,
        queueWaitTimeChanged_,
        dequeueWaitTimeChanged,
        dequeueWaitTimeChanged_,
        queueRateChanged,
        queueRateChanged_,
        -- * Basic Signals
        enqueueStored,
        dequeueRequested,
        dequeueExtracted,
        -- * Overall Signal
        queueChanged_) where

import Data.IORef
import Data.Monoid
import Data.Maybe

import Control.Monad
import Control.Monad.Trans

import Simulation.Aivika.Internal.Specs
import Simulation.Aivika.Internal.Simulation
import Simulation.Aivika.Internal.Dynamics
import Simulation.Aivika.Internal.Event
import Simulation.Aivika.Internal.Process
import Simulation.Aivika.Signal
import Simulation.Aivika.Resource.Base
import Simulation.Aivika.QueueStrategy
import Simulation.Aivika.Statistics

import qualified Simulation.Aivika.DoubleLinkedList as DLL 
import qualified Simulation.Aivika.Vector as V
import qualified Simulation.Aivika.PriorityQueue as PQ

-- | A type synonym for the ordinary FIFO queue also known as the FCFS
-- (First Come - First Serviced) queue.
type FCFSQueue a = Queue FCFS FCFS a

-- | A type synonym for the ordinary LIFO queue also known as the LCFS
-- (Last Come - First Serviced) queue.
type LCFSQueue a = Queue LCFS FCFS a

-- | A type synonym for the SIRO (Serviced in Random Order) queue.
type SIROQueue a = Queue SIRO FCFS a

-- | A type synonym for the queue with static priorities applied when
-- storing the elements in the queue.
type PriorityQueue a = Queue StaticPriorities FCFS a

-- | Represents an infinite queue using the specified strategies for
-- internal storing (in memory), @sm@, and dequeueing (output), @so@, where @a@ denotes
-- the type of items stored in the queue.
data Queue sm so a =
  Queue { forall sm so a. Queue sm so a -> sm
enqueueStoringStrategy :: sm,
          -- ^ The strategy applied when storing (in memory) items in the queue.
          forall sm so a. Queue sm so a -> so
dequeueStrategy :: so,
          -- ^ The strategy applied to the dequeueing (output) processes.
          forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore :: StrategyQueue sm (QueueItem a),
          forall sm so a. Queue sm so a -> Resource so
dequeueRes :: Resource so,
          forall sm so a. Queue sm so a -> IORef Int
queueCountRef :: IORef Int,
          forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef :: IORef (TimingStats Int),
          forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef :: IORef Int,
          forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef :: IORef Int,
          forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef :: IORef Int,
          forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef :: IORef (SamplingStats Double),
          forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef :: IORef (SamplingStats Double),
          forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource :: SignalSource a,
          forall sm so a. Queue sm so a -> SignalSource ()
dequeueRequestedSource :: SignalSource (),
          forall sm so a. Queue sm so a -> SignalSource a
dequeueExtractedSource :: SignalSource a }

-- | Stores the item and a time of its enqueuing. 
data QueueItem a =
  QueueItem { forall a. QueueItem a -> a
itemValue :: a,
              -- ^ Return the item value.
              forall a. QueueItem a -> Double
itemStoringTime :: Double
              -- ^ Return the time of storing in the queue.
            }
  
-- | Create a new infinite FCFS queue.  
newFCFSQueue :: Event (FCFSQueue a)  
newFCFSQueue :: forall a. Event (FCFSQueue a)
newFCFSQueue = forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue FCFS
FCFS FCFS
FCFS
  
-- | Create a new infinite LCFS queue.  
newLCFSQueue :: Event (LCFSQueue a)  
newLCFSQueue :: forall a. Event (LCFSQueue a)
newLCFSQueue = forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue LCFS
LCFS FCFS
FCFS
  
-- | Create a new infinite SIRO queue.  
newSIROQueue :: Event (SIROQueue a)  
newSIROQueue :: forall a. Event (SIROQueue a)
newSIROQueue = forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue SIRO
SIRO FCFS
FCFS
  
-- | Create a new infinite priority queue.  
newPriorityQueue :: Event (PriorityQueue a)  
newPriorityQueue :: forall a. Event (PriorityQueue a)
newPriorityQueue = forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue StaticPriorities
StaticPriorities FCFS
FCFS
  
-- | Create a new infinite queue with the specified strategies.  
newQueue :: (QueueStrategy sm,
             QueueStrategy so) =>
            sm
            -- ^ the strategy applied when storing items in the queue
            -> so
            -- ^ the strategy applied to the dequeueing (output) processes when the queue is empty
            -> Event (Queue sm so a)  
newQueue :: forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue sm
sm so
so =
  do Double
t  <- forall (m :: * -> *) a. DynamicsLift m => Dynamics a -> m a
liftDynamics Dynamics Double
time
     IORef Int
i  <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef Int
0
     IORef (TimingStats Int)
is <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef forall a b. (a -> b) -> a -> b
$ forall a. TimingData a => Double -> a -> TimingStats a
returnTimingStats Double
t Int
0
     IORef Int
cm <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef Int
0
     IORef Int
cr <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef Int
0
     IORef Int
co <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef Int
0
     StrategyQueue sm (QueueItem a)
qm <- forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation forall a b. (a -> b) -> a -> b
$ forall s i. QueueStrategy s => s -> Simulation (StrategyQueue s i)
newStrategyQueue sm
sm
     Resource so
ro <- forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation forall a b. (a -> b) -> a -> b
$ forall s.
QueueStrategy s =>
s -> Int -> Maybe Int -> Simulation (Resource s)
newResourceWithMaxCount so
so Int
0 forall a. Maybe a
Nothing
     IORef (SamplingStats Double)
w  <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef forall a. Monoid a => a
mempty
     IORef (SamplingStats Double)
wo <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef forall a. Monoid a => a
mempty 
     SignalSource a
s3 <- forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation forall a. Simulation (SignalSource a)
newSignalSource
     SignalSource ()
s4 <- forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation forall a. Simulation (SignalSource a)
newSignalSource
     SignalSource a
s5 <- forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation forall a. Simulation (SignalSource a)
newSignalSource
     forall (m :: * -> *) a. Monad m => a -> m a
return Queue { enqueueStoringStrategy :: sm
enqueueStoringStrategy = sm
sm,
                    dequeueStrategy :: so
dequeueStrategy = so
so,
                    queueStore :: StrategyQueue sm (QueueItem a)
queueStore = StrategyQueue sm (QueueItem a)
qm,
                    dequeueRes :: Resource so
dequeueRes = Resource so
ro,
                    queueCountRef :: IORef Int
queueCountRef = IORef Int
i,
                    queueCountStatsRef :: IORef (TimingStats Int)
queueCountStatsRef = IORef (TimingStats Int)
is,
                    enqueueStoreCountRef :: IORef Int
enqueueStoreCountRef = IORef Int
cm,
                    dequeueCountRef :: IORef Int
dequeueCountRef = IORef Int
cr,
                    dequeueExtractCountRef :: IORef Int
dequeueExtractCountRef = IORef Int
co,
                    queueWaitTimeRef :: IORef (SamplingStats Double)
queueWaitTimeRef = IORef (SamplingStats Double)
w,
                    dequeueWaitTimeRef :: IORef (SamplingStats Double)
dequeueWaitTimeRef = IORef (SamplingStats Double)
wo,
                    enqueueStoredSource :: SignalSource a
enqueueStoredSource = SignalSource a
s3,
                    dequeueRequestedSource :: SignalSource ()
dequeueRequestedSource = SignalSource ()
s4,
                    dequeueExtractedSource :: SignalSource a
dequeueExtractedSource = SignalSource a
s5 }

-- | Test whether the queue is empty.
--
-- See also 'queueNullChanged' and 'queueNullChanged_'.
queueNull :: Queue sm so a -> Event Bool
queueNull :: forall sm so a. Queue sm so a -> Event Bool
queueNull Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do Int
n <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
     forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n forall a. Eq a => a -> a -> Bool
== Int
0)
  
-- | Signal when the 'queueNull' property value has changed.
queueNullChanged :: Queue sm so a -> Signal Bool
queueNullChanged :: forall sm so a. Queue sm so a -> Signal Bool
queueNullChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Bool
queueNull Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
queueNullChanged_ Queue sm so a
q)
  
-- | Signal when the 'queueNull' property value has changed.
queueNullChanged_ :: Queue sm so a -> Signal ()
queueNullChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueNullChanged_ = forall sm so a. Queue sm so a -> Signal ()
queueCountChanged_

-- | Return the current queue size.
--
-- See also 'queueCountStats', 'queueCountChanged' and 'queueCountChanged_'.
queueCount :: Queue sm so a -> Event Int
queueCount :: forall sm so a. Queue sm so a -> Event Int
queueCount Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)

-- | Return the queue size statistics.
queueCountStats :: Queue sm so a -> Event (TimingStats Int)
queueCountStats :: forall sm so a. Queue sm so a -> Event (TimingStats Int)
queueCountStats Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q)
  
-- | Signal when the 'queueCount' property value has changed.
queueCountChanged :: Queue sm so a -> Signal Int
queueCountChanged :: forall sm so a. Queue sm so a -> Signal Int
queueCountChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Int
queueCount Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
queueCountChanged_ Queue sm so a
q)
  
-- | Signal when the 'queueCount' property value has changed.
queueCountChanged_ :: Queue sm so a -> Signal ()
queueCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueCountChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q) forall a. Semigroup a => a -> a -> a
<>
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
      
-- | Return the total number of input items that were stored.
--
-- See also 'enqueueStoreCountChanged' and 'enqueueStoreCountChanged_'.
enqueueStoreCount :: Queue sm so a -> Event Int
enqueueStoreCount :: forall sm so a. Queue sm so a -> Event Int
enqueueStoreCount Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q)
  
-- | Signal when the 'enqueueStoreCount' property value has changed.
enqueueStoreCountChanged :: Queue sm so a -> Signal Int
enqueueStoreCountChanged :: forall sm so a. Queue sm so a -> Signal Int
enqueueStoreCountChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Int
enqueueStoreCount Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
enqueueStoreCountChanged_ Queue sm so a
q)
  
-- | Signal when the 'enqueueStoreCount' property value has changed.
enqueueStoreCountChanged_ :: Queue sm so a -> Signal ()
enqueueStoreCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
enqueueStoreCountChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q)
      
-- | Return the total number of requests for dequeueing the items,
-- not taking into account the failed attempts to dequeue immediately
-- without suspension.
--
-- See also 'dequeueCountChanged' and 'dequeueCountChanged_'.
dequeueCount :: Queue sm so a -> Event Int
dequeueCount :: forall sm so a. Queue sm so a -> Event Int
dequeueCount Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q)
      
-- | Signal when the 'dequeueCount' property value has changed.
dequeueCountChanged :: Queue sm so a -> Signal Int
dequeueCountChanged :: forall sm so a. Queue sm so a -> Signal Int
dequeueCountChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Int
dequeueCount Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
dequeueCountChanged_ Queue sm so a
q)
  
-- | Signal when the 'dequeueCount' property value has changed.
dequeueCountChanged_ :: Queue sm so a -> Signal ()
dequeueCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
dequeueCountChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal ()
dequeueRequested Queue sm so a
q)
      
-- | Return the total number of output items that were actually dequeued.
--
-- See also 'dequeueExtractCountChanged' and 'dequeueExtractCountChanged_'.
dequeueExtractCount :: Queue sm so a -> Event Int
dequeueExtractCount :: forall sm so a. Queue sm so a -> Event Int
dequeueExtractCount Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q)
      
-- | Signal when the 'dequeueExtractCount' property value has changed.
dequeueExtractCountChanged :: Queue sm so a -> Signal Int
dequeueExtractCountChanged :: forall sm so a. Queue sm so a -> Signal Int
dequeueExtractCountChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Int
dequeueExtractCount Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
dequeueExtractCountChanged_ Queue sm so a
q)
  
-- | Signal when the 'dequeueExtractCount' property value has changed.
dequeueExtractCountChanged_ :: Queue sm so a -> Signal ()
dequeueExtractCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
dequeueExtractCountChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)

-- | Return the rate of the items that were stored: how many items
-- per time.
enqueueStoreRate :: Queue sm so a -> Event Double
enqueueStoreRate :: forall sm so a. Queue sm so a -> Event Double
enqueueStoreRate Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do Int
x <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q)
     let t0 :: Double
t0 = Specs -> Double
spcStartTime forall a b. (a -> b) -> a -> b
$ Point -> Specs
pointSpecs Point
p
         t :: Double
t  = Point -> Double
pointTime Point
p
     forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x forall a. Fractional a => a -> a -> a
/ (Double
t forall a. Num a => a -> a -> a
- Double
t0))
      
-- | 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 sm so a -> Event Double
dequeueRate :: forall sm so a. Queue sm so a -> Event Double
dequeueRate Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do Int
x <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q)
     let t0 :: Double
t0 = Specs -> Double
spcStartTime forall a b. (a -> b) -> a -> b
$ Point -> Specs
pointSpecs Point
p
         t :: Double
t  = Point -> Double
pointTime Point
p
     forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x forall a. Fractional a => a -> a -> a
/ (Double
t forall a. Num a => a -> a -> a
- Double
t0))
      
-- | Return the rate of the output items that were dequeued: how many items
-- per time.
dequeueExtractRate :: Queue sm so a -> Event Double
dequeueExtractRate :: forall sm so a. Queue sm so a -> Event Double
dequeueExtractRate Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do Int
x <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q)
     let t0 :: Double
t0 = Specs -> Double
spcStartTime forall a b. (a -> b) -> a -> b
$ Point -> Specs
pointSpecs Point
p
         t :: Double
t  = Point -> Double
pointTime Point
p
     forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x forall a. Fractional a => a -> a -> a
/ (Double
t forall a. Num a => a -> a -> a
- Double
t0))
      
-- | Return the wait time from the time at which the item was stored in the queue to
-- the time at which it was dequeued.
--
-- See also 'queueWaitTimeChanged' and 'queueWaitTimeChanged_'.
queueWaitTime :: Queue sm so a -> Event (SamplingStats Double)
queueWaitTime :: forall sm so a. Queue sm so a -> Event (SamplingStats Double)
queueWaitTime Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q)
      
-- | Signal when the 'queueWaitTime' property value has changed.
queueWaitTimeChanged :: Queue sm so a -> Signal (SamplingStats Double)
queueWaitTimeChanged :: forall sm so a. Queue sm so a -> Signal (SamplingStats Double)
queueWaitTimeChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event (SamplingStats Double)
queueWaitTime Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
queueWaitTimeChanged_ Queue sm so a
q)
  
-- | Signal when the 'queueWaitTime' property value has changed.
queueWaitTimeChanged_ :: Queue sm so a -> Signal ()
queueWaitTimeChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueWaitTimeChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
      
-- | 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.
--
-- See also 'dequeueWaitTimeChanged' and 'dequeueWaitTimeChanged_'.
dequeueWaitTime :: Queue sm so a -> Event (SamplingStats Double)
dequeueWaitTime :: forall sm so a. Queue sm so a -> Event (SamplingStats Double)
dequeueWaitTime Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p -> forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef Queue sm so a
q)
      
-- | Signal when the 'dequeueWaitTime' property value has changed.
dequeueWaitTimeChanged :: Queue sm so a -> Signal (SamplingStats Double)
dequeueWaitTimeChanged :: forall sm so a. Queue sm so a -> Signal (SamplingStats Double)
dequeueWaitTimeChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event (SamplingStats Double)
dequeueWaitTime Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
dequeueWaitTimeChanged_ Queue sm so a
q)
  
-- | Signal when the 'dequeueWaitTime' property value has changed.
dequeueWaitTimeChanged_ :: Queue sm so a -> Signal ()
dequeueWaitTimeChanged_ :: forall sm so a. Queue sm so a -> Signal ()
dequeueWaitTimeChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)

-- | Return a long-term average queue rate calculated as
-- the average queue size divided by the average wait time.
--
-- See also 'queueRateChanged' and 'queueRateChanged_'.
queueRate :: Queue sm so a -> Event Double
queueRate :: forall sm so a. Queue sm so a -> Event Double
queueRate Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do TimingStats Int
x <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q)
     SamplingStats Double
y <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q)
     forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. TimingData a => TimingStats a -> Double
timingStatsMean TimingStats Int
x forall a. Fractional a => a -> a -> a
/ forall a. SamplingStats a -> Double
samplingStatsMean SamplingStats Double
y) 

-- | Signal when the 'queueRate' property value has changed.
queueRateChanged :: Queue sm so a -> Signal Double
queueRateChanged :: forall sm so a. Queue sm so a -> Signal Double
queueRateChanged Queue sm so a
q =
  forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Double
queueRate Queue sm so a
q) (forall sm so a. Queue sm so a -> Signal ()
queueRateChanged_ Queue sm so a
q)

-- | Signal when the 'queueRate' property value has changed.
queueRateChanged_ :: Queue sm so a -> Signal ()
queueRateChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueRateChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q) forall a. Semigroup a => a -> a -> a
<>
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
  
-- | Dequeue suspending the process if the queue is empty.
dequeue :: (DequeueStrategy sm,
            EnqueueStrategy so)
           => Queue sm so a
           -- ^ the queue
           -> Process a
           -- ^ the dequeued value
dequeue :: forall sm so a.
(DequeueStrategy sm, EnqueueStrategy so) =>
Queue sm so a -> Process a
dequeue Queue sm so a
q =
  do Double
t <- forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
     forall s. EnqueueStrategy s => Resource s -> Process ()
requestResource (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
     forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent forall a b. (a -> b) -> a -> b
$ forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t
  
-- | Dequeue with the output priority suspending the process if the queue is empty.
dequeueWithOutputPriority :: (DequeueStrategy sm,
                              PriorityQueueStrategy so po)
                             => Queue sm so a
                             -- ^ the queue
                             -> po
                             -- ^ the priority for output
                             -> Process a
                             -- ^ the dequeued value
dequeueWithOutputPriority :: forall sm so po a.
(DequeueStrategy sm, PriorityQueueStrategy so po) =>
Queue sm so a -> po -> Process a
dequeueWithOutputPriority Queue sm so a
q po
po =
  do Double
t <- forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent forall a b. (a -> b) -> a -> b
$ forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
     forall s p.
PriorityQueueStrategy s p =>
Resource s -> p -> Process ()
requestResourceWithPriority (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q) po
po
     forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent forall a b. (a -> b) -> a -> b
$ forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t
  
-- | Try to dequeue immediately.
tryDequeue :: DequeueStrategy sm
              => Queue sm so a
              -- ^ the queue
              -> Event (Maybe a)
              -- ^ the dequeued value of 'Nothing'
tryDequeue :: forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Event (Maybe a)
tryDequeue Queue sm so a
q =
  do Bool
x <- forall s. Resource s -> Event Bool
tryRequestResourceWithinEvent (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
     if Bool
x 
       then do Double
t <- forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
               forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t
       else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing

-- | Remove the item from the queue and return a flag indicating
-- whether the item was found and actually removed.
queueDelete :: (Eq a,
                DeletingQueueStrategy sm,
                DequeueStrategy so)
               => Queue sm so a
               -- ^ the queue
               -> a
               -- ^ the item to remove from the queue
               -> Event Bool
               -- ^ whether the item was found and removed
queueDelete :: forall a sm so.
(Eq a, DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event Bool
queueDelete Queue sm so a
q a
a = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Maybe a -> Bool
isJust forall a b. (a -> b) -> a -> b
$ forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueDeleteBy Queue sm so a
q (forall a. Eq a => a -> a -> Bool
== a
a)

-- | Remove the specified item from the queue.
queueDelete_ :: (Eq a,
                 DeletingQueueStrategy sm,
                 DequeueStrategy so)
                => Queue sm so a
                -- ^ the queue
                -> a
                -- ^ the item to remove from the queue
                -> Event ()
queueDelete_ :: forall a sm so.
(Eq a, DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event ()
queueDelete_ Queue sm so a
q a
a = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> b -> a
const ()) forall a b. (a -> b) -> a -> b
$ forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueDeleteBy Queue sm so a
q (forall a. Eq a => a -> a -> Bool
== a
a)

-- | Remove an item satisfying the specified predicate and return the item if found.
queueDeleteBy :: (DeletingQueueStrategy sm,
                  DequeueStrategy so)
                 => Queue sm so a
                 -- ^ the queue
                 -> (a -> Bool)
                 -- ^ the predicate
                 -> Event (Maybe a)
queueDeleteBy :: forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueDeleteBy Queue sm so a
q a -> Bool
pred =
  do Bool
x <- forall s. Resource s -> Event Bool
tryRequestResourceWithinEvent (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
     if Bool
x
       then do Maybe (QueueItem a)
i <- forall s i.
DeletingQueueStrategy s =>
StrategyQueue s i -> (i -> Bool) -> Event (Maybe i)
strategyQueueDeleteBy (forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) (a -> Bool
pred forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. QueueItem a -> a
itemValue)
               case Maybe (QueueItem a)
i of
                 Maybe (QueueItem a)
Nothing ->
                   do forall s. DequeueStrategy s => Resource s -> Event ()
releaseResourceWithinEvent (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
                      forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
                 Just QueueItem a
i ->
                   do Double
t <- forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
                      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> QueueItem a -> Event a
dequeuePostExtract Queue sm so a
q Double
t QueueItem a
i
       else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
               
-- | Remove an item satisfying the specified predicate.
queueDeleteBy_ :: (DeletingQueueStrategy sm,
                   DequeueStrategy so)
                  => Queue sm so a
                  -- ^ the queue
                  -> (a -> Bool)
                  -- ^ the predicate
                  -> Event ()
queueDeleteBy_ :: forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event ()
queueDeleteBy_ Queue sm so a
q a -> Bool
pred = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> b -> a
const ()) forall a b. (a -> b) -> a -> b
$ forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueDeleteBy Queue sm so a
q a -> Bool
pred

-- | Detect whether the item is contained in the queue.
queueContains :: (Eq a,
                  DeletingQueueStrategy sm)
                 => Queue sm so a
                 -- ^ the queue
                 -> a
                 -- ^ the item to search the queue for
                 -> Event Bool
                 -- ^ whether the item was found
queueContains :: forall a sm so.
(Eq a, DeletingQueueStrategy sm) =>
Queue sm so a -> a -> Event Bool
queueContains Queue sm so a
q a
a = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Maybe a -> Bool
isJust forall a b. (a -> b) -> a -> b
$ forall sm so a.
DeletingQueueStrategy sm =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueContainsBy Queue sm so a
q (forall a. Eq a => a -> a -> Bool
== a
a)

-- | Detect whether an item satisfying the specified predicate is contained in the queue.
queueContainsBy :: DeletingQueueStrategy sm
                   => Queue sm so a
                   -- ^ the queue
                   -> (a -> Bool)
                   -- ^ the predicate
                   -> Event (Maybe a)
                   -- ^ the item if it was found
queueContainsBy :: forall sm so a.
DeletingQueueStrategy sm =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueContainsBy Queue sm so a
q a -> Bool
pred =
  do Maybe (QueueItem a)
x <- forall s i.
DeletingQueueStrategy s =>
StrategyQueue s i -> (i -> Bool) -> Event (Maybe i)
strategyQueueContainsBy (forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) (a -> Bool
pred forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. QueueItem a -> a
itemValue)
     case Maybe (QueueItem a)
x of
       Maybe (QueueItem a)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
       Just QueueItem a
i  -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (forall a. QueueItem a -> a
itemValue QueueItem a
i)

-- | Clear the queue immediately.
clearQueue :: DequeueStrategy sm
              => Queue sm so a
              -- ^ the queue
              -> Event ()
clearQueue :: forall sm so a. DequeueStrategy sm => Queue sm so a -> Event ()
clearQueue Queue sm so a
q =
  do Maybe a
x <- forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Event (Maybe a)
tryDequeue Queue sm so a
q
     case Maybe a
x of
       Maybe a
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
       Just a
a  -> forall sm so a. DequeueStrategy sm => Queue sm so a -> Event ()
clearQueue Queue sm so a
q

-- | Enqueue the item.  
enqueue :: (EnqueueStrategy sm,
            DequeueStrategy so)
           => Queue sm so a
           -- ^ the queue
           -> a
           -- ^ the item to enqueue
           -> Event ()
enqueue :: forall sm so a.
(EnqueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event ()
enqueue = forall sm so a.
(EnqueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event ()
enqueueStore
     
-- | Enqueue with the storing priority the item.  
enqueueWithStoringPriority :: (PriorityQueueStrategy sm pm,
                               DequeueStrategy so)
                              => Queue sm so a
                              -- ^ the queue
                              -> pm
                              -- ^ the priority for storing
                              -> a
                              -- ^ the item to enqueue
                              -> Event ()
enqueueWithStoringPriority :: forall sm pm so a.
(PriorityQueueStrategy sm pm, DequeueStrategy so) =>
Queue sm so a -> pm -> a -> Event ()
enqueueWithStoringPriority = forall sm pm so a.
(PriorityQueueStrategy sm pm, DequeueStrategy so) =>
Queue sm so a -> pm -> a -> Event ()
enqueueStoreWithPriority

-- | Return a signal that notifies when the enqueued item
-- is stored in the internal memory of the queue.
enqueueStored :: Queue sm so a -> Signal a
enqueueStored :: forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q = forall a. SignalSource a -> Signal a
publishSignal (forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource Queue sm so a
q)

-- | Return a signal that notifies when the dequeuing operation was requested.
dequeueRequested :: Queue sm so a -> Signal ()
dequeueRequested :: forall sm so a. Queue sm so a -> Signal ()
dequeueRequested Queue sm so a
q = forall a. SignalSource a -> Signal a
publishSignal (forall sm so a. Queue sm so a -> SignalSource ()
dequeueRequestedSource Queue sm so a
q)

-- | Return a signal that notifies when the item was extracted from the internal
-- storage of the queue and prepared for immediate receiving by the dequeuing process.
dequeueExtracted :: Queue sm so a -> Signal a
dequeueExtracted :: forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q = forall a. SignalSource a -> Signal a
publishSignal (forall sm so a. Queue sm so a -> SignalSource a
dequeueExtractedSource Queue sm so a
q)

-- | Store the item.
enqueueStore :: (EnqueueStrategy sm,
                 DequeueStrategy so)
                => Queue sm so a
                -- ^ the queue
                -> a
                -- ^ the item to be stored
                -> Event ()
enqueueStore :: forall sm so a.
(EnqueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event ()
enqueueStore Queue sm so a
q a
a =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do let i :: QueueItem a
i = QueueItem { itemValue :: a
itemValue = a
a,
                         itemStoringTime :: Double
itemStoringTime = Point -> Double
pointTime Point
p }
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall s i. EnqueueStrategy s => StrategyQueue s i -> i -> Event ()
strategyEnqueue (forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) QueueItem a
i
     Int
c <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
     let c' :: Int
c' = Int
c forall a. Num a => a -> a -> a
+ Int
1
         t :: Double
t  = Point -> Double
pointTime Point
p
     Int
c' seq :: forall a b. a -> b -> b
`seq` forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q) Int
c'
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (forall a.
TimingData a =>
Double -> a -> TimingStats a -> TimingStats a
addTimingStats Double
t Int
c')
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q) (forall a. Num a => a -> a -> a
+ Int
1)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall s. DequeueStrategy s => Resource s -> Event ()
releaseResourceWithinEvent (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall a. SignalSource a -> a -> Event ()
triggerSignal (forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource Queue sm so a
q) (forall a. QueueItem a -> a
itemValue QueueItem a
i)

-- | Store with the priority the item.
enqueueStoreWithPriority :: (PriorityQueueStrategy sm pm,
                             DequeueStrategy so)
                            => Queue sm so a
                            -- ^ the queue
                            -> pm
                            -- ^ the priority for storing
                            -> a
                            -- ^ the item to be enqueued
                            -> Event ()
enqueueStoreWithPriority :: forall sm pm so a.
(PriorityQueueStrategy sm pm, DequeueStrategy so) =>
Queue sm so a -> pm -> a -> Event ()
enqueueStoreWithPriority Queue sm so a
q pm
pm a
a =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do let i :: QueueItem a
i = QueueItem { itemValue :: a
itemValue = a
a,
                         itemStoringTime :: Double
itemStoringTime = Point -> Double
pointTime Point
p }
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall s p i.
PriorityQueueStrategy s p =>
StrategyQueue s i -> p -> i -> Event ()
strategyEnqueueWithPriority (forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) pm
pm QueueItem a
i
     Int
c <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
     let c' :: Int
c' = Int
c forall a. Num a => a -> a -> a
+ Int
1
         t :: Double
t  = Point -> Double
pointTime Point
p
     Int
c' seq :: forall a b. a -> b -> b
`seq` forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q) Int
c'
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (forall a.
TimingData a =>
Double -> a -> TimingStats a -> TimingStats a
addTimingStats Double
t Int
c')
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q) (forall a. Num a => a -> a -> a
+ Int
1)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall s. DequeueStrategy s => Resource s -> Event ()
releaseResourceWithinEvent (forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall a. SignalSource a -> a -> Event ()
triggerSignal (forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource Queue sm so a
q) (forall a. QueueItem a -> a
itemValue QueueItem a
i)

-- | Accept the dequeuing request and return the current simulation time.
dequeueRequest :: Queue sm so a
                 -- ^ the queue
                 -> Event Double
                 -- ^ the current time
dequeueRequest :: forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q) (forall a. Num a => a -> a -> a
+ Int
1)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall a. SignalSource a -> a -> Event ()
triggerSignal (forall sm so a. Queue sm so a -> SignalSource ()
dequeueRequestedSource Queue sm so a
q) ()
     forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Point -> Double
pointTime Point
p 

-- | Extract an item for the dequeuing request.  
dequeueExtract :: DequeueStrategy sm
                  => Queue sm so a
                  -- ^ the queue
                  -> Double
                  -- ^ the time of the dequeuing request
                  -> Event a
                  -- ^ the dequeued value
dequeueExtract :: forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t' =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do QueueItem a
i <- forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
          forall s i. DequeueStrategy s => StrategyQueue s i -> Event i
strategyDequeue (forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> QueueItem a -> Event a
dequeuePostExtract Queue sm so a
q Double
t' QueueItem a
i

-- | A post action after extracting the item by the dequeuing request.  
dequeuePostExtract :: DequeueStrategy sm
                      => Queue sm so a
                      -- ^ the queue
                      -> Double
                      -- ^ the time of the dequeuing request
                      -> QueueItem a
                      -- ^ the item to dequeue
                      -> Event a
                      -- ^ the dequeued value
dequeuePostExtract :: forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> QueueItem a -> Event a
dequeuePostExtract Queue sm so a
q Double
t' QueueItem a
i =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do Int
c <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
     let c' :: Int
c' = Int
c forall a. Num a => a -> a -> a
- Int
1
         t :: Double
t  = Point -> Double
pointTime Point
p
     Int
c' seq :: forall a b. a -> b -> b
`seq` forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q) Int
c'
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (forall a.
TimingData a =>
Double -> a -> TimingStats a -> TimingStats a
addTimingStats Double
t Int
c')
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q) (forall a. Num a => a -> a -> a
+ Int
1)
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall sm so a. Queue sm so a -> Double -> QueueItem a -> Event ()
dequeueStat Queue sm so a
q Double
t' QueueItem a
i
     forall a. Point -> Event a -> IO a
invokeEvent Point
p forall a b. (a -> b) -> a -> b
$
       forall a. SignalSource a -> a -> Event ()
triggerSignal (forall sm so a. Queue sm so a -> SignalSource a
dequeueExtractedSource Queue sm so a
q) (forall a. QueueItem a -> a
itemValue QueueItem a
i)
     forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. QueueItem a -> a
itemValue QueueItem a
i

-- | Update the statistics for the output wait time of the dequeuing operation
-- and the wait time of storing in the queue.
dequeueStat :: Queue sm so a
               -- ^ the queue
               -> Double
               -- ^ the time of the dequeuing request
               -> QueueItem a
               -- ^ the item and its input time
               -> Event ()
               -- ^ the action of updating the statistics
dequeueStat :: forall sm so a. Queue sm so a -> Double -> QueueItem a -> Event ()
dequeueStat Queue sm so a
q Double
t' QueueItem a
i =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do let t1 :: Double
t1 = forall a. QueueItem a -> Double
itemStoringTime QueueItem a
i
         t :: Double
t  = Point -> Double
pointTime Point
p
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef Queue sm so a
q) forall a b. (a -> b) -> a -> b
$
       forall a. SamplingData a => a -> SamplingStats a -> SamplingStats a
addSamplingStats (Double
t forall a. Num a => a -> a -> a
- Double
t')
     forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q) forall a b. (a -> b) -> a -> b
$
       forall a. SamplingData a => a -> SamplingStats a -> SamplingStats a
addSamplingStats (Double
t forall a. Num a => a -> a -> a
- Double
t1)

-- | Signal whenever any property of the queue changes.
--
-- The property must have the corresponded signal. There are also characteristics
-- similar to the properties but that have no signals. As a rule, such characteristics
-- already depend on the simulation time and therefore they may change at any
-- time point.
queueChanged_ :: Queue sm so a -> Signal ()
queueChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueChanged_ Queue sm so a
q =
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q) forall a. Semigroup a => a -> a -> a
<>
  forall sm so a. Queue sm so a -> Signal ()
dequeueRequested Queue sm so a
q forall a. Semigroup a => a -> a -> a
<>
  forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (forall a b. a -> b -> a
const ()) (forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)

-- | Return the summary for the queue with desciption of its
-- properties and activities using the specified indent.
queueSummary :: (Show sm, Show so) => Queue sm so a -> Int -> Event ShowS
queueSummary :: forall sm so a.
(Show sm, Show so) =>
Queue sm so a -> Int -> Event ShowS
queueSummary Queue sm so a
q Int
indent =
  do let sm :: sm
sm = forall sm so a. Queue sm so a -> sm
enqueueStoringStrategy Queue sm so a
q
         so :: so
so = forall sm so a. Queue sm so a -> so
dequeueStrategy Queue sm so a
q
     Bool
null <- forall sm so a. Queue sm so a -> Event Bool
queueNull Queue sm so a
q
     Int
count <- forall sm so a. Queue sm so a -> Event Int
queueCount Queue sm so a
q
     TimingStats Int
countStats <- forall sm so a. Queue sm so a -> Event (TimingStats Int)
queueCountStats Queue sm so a
q
     Int
enqueueStoreCount <- forall sm so a. Queue sm so a -> Event Int
enqueueStoreCount Queue sm so a
q
     Int
dequeueCount <- forall sm so a. Queue sm so a -> Event Int
dequeueCount Queue sm so a
q
     Int
dequeueExtractCount <- forall sm so a. Queue sm so a -> Event Int
dequeueExtractCount Queue sm so a
q
     Double
enqueueStoreRate <- forall sm so a. Queue sm so a -> Event Double
enqueueStoreRate Queue sm so a
q
     Double
dequeueRate <- forall sm so a. Queue sm so a -> Event Double
dequeueRate Queue sm so a
q
     Double
dequeueExtractRate <- forall sm so a. Queue sm so a -> Event Double
dequeueExtractRate Queue sm so a
q
     SamplingStats Double
waitTime <- forall sm so a. Queue sm so a -> Event (SamplingStats Double)
queueWaitTime Queue sm so a
q
     SamplingStats Double
dequeueWaitTime <- forall sm so a. Queue sm so a -> Event (SamplingStats Double)
dequeueWaitTime Queue sm so a
q
     let tab :: [Char]
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the storing (memory) strategy = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows sm
sm forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the dequeueing (output) strategy = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows so
so forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"empty? = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the current size = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Int
count forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the size statistics = \n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. (Show a, TimingData a) => TimingStats a -> Int -> ShowS
timingStatsSummary TimingStats Int
countStats (Int
2 forall a. Num a => a -> a -> a
+ Int
indent) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the enqueue store count (number of the input items that were stored) = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Int
enqueueStoreCount forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the dequeue count (number of requests for dequeueing an item) = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Int
dequeueCount forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the dequeue extract count (number of the output items that were dequeued) = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Int
dequeueExtractCount forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the enqueue store rate (how many input items were stored per time) = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Double
enqueueStoreRate forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the dequeue rate (how many requests for dequeueing per time) = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Double
dequeueRate forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the dequeue extract rate (how many output items were dequeued per time) = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => a -> ShowS
shows Double
dequeueExtractRate forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the wait time (when was stored -> when was dequeued) = \n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => SamplingStats a -> Int -> ShowS
samplingStatsSummary SamplingStats Double
waitTime (Int
2 forall a. Num a => a -> a -> a
+ Int
indent) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"\n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       [Char] -> ShowS
showString [Char]
"the dequeue wait time (when was requested for dequeueing -> when was dequeued) = \n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       forall a. Show a => SamplingStats a -> Int -> ShowS
samplingStatsSummary SamplingStats Double
dequeueWaitTime (Int
2 forall a. Num a => a -> a -> a
+ Int
indent)

-- | Reset the statistics.
resetQueue :: Queue sm so a -> Event ()
resetQueue :: forall sm so a. Queue sm so a -> Event ()
resetQueue Queue sm so a
q =
  forall a. (Point -> IO a) -> Event a
Event forall a b. (a -> b) -> a -> b
$ \Point
p ->
  do let t :: Double
t = Point -> Double
pointTime Point
p
     Int
queueCount <- forall a. IORef a -> IO a
readIORef (forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
     forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) forall a b. (a -> b) -> a -> b
$
       forall a. TimingData a => Double -> a -> TimingStats a
returnTimingStats Double
t Int
queueCount
     forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q) Int
0
     forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q) Int
0
     forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q) Int
0
     forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q) forall a. Monoid a => a
mempty
     forall a. IORef a -> a -> IO ()
writeIORef (forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef Queue sm so a
q) forall a. Monoid a => a
mempty