module Simulation.Aivika.Queue.Infinite
(
FCFSQueue,
LCFSQueue,
SIROQueue,
PriorityQueue,
Queue,
newFCFSQueue,
newLCFSQueue,
newSIROQueue,
newPriorityQueue,
newQueue,
enqueueStoringStrategy,
dequeueStrategy,
queueNull,
queueCount,
queueCountStats,
enqueueStoreCount,
dequeueCount,
dequeueExtractCount,
enqueueStoreRate,
dequeueRate,
dequeueExtractRate,
queueWaitTime,
dequeueWaitTime,
queueRate,
dequeue,
dequeueWithOutputPriority,
tryDequeue,
enqueue,
enqueueWithStoringPriority,
queueDelete,
queueDelete_,
queueDeleteBy,
queueDeleteBy_,
queueContains,
queueContainsBy,
clearQueue,
resetQueue,
queueSummary,
queueNullChanged,
queueNullChanged_,
queueCountChanged,
queueCountChanged_,
enqueueStoreCountChanged,
enqueueStoreCountChanged_,
dequeueCountChanged,
dequeueCountChanged_,
dequeueExtractCountChanged,
dequeueExtractCountChanged_,
queueWaitTimeChanged,
queueWaitTimeChanged_,
dequeueWaitTimeChanged,
dequeueWaitTimeChanged_,
queueRateChanged,
queueRateChanged_,
enqueueStored,
dequeueRequested,
dequeueExtracted,
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
type FCFSQueue a = Queue FCFS FCFS a
type LCFSQueue a = Queue LCFS FCFS a
type SIROQueue a = Queue SIRO FCFS a
type PriorityQueue a = Queue StaticPriorities FCFS a
data Queue sm so a =
Queue { forall sm so a. Queue sm so a -> sm
enqueueStoringStrategy :: sm,
forall sm so a. Queue sm so a -> so
dequeueStrategy :: so,
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,
:: 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 (),
:: SignalSource a }
data QueueItem a =
QueueItem { forall a. QueueItem a -> a
itemValue :: a,
forall a. QueueItem a -> Double
itemStoringTime :: Double
}
newFCFSQueue :: Event (FCFSQueue a)
newFCFSQueue :: forall a. Event (FCFSQueue a)
newFCFSQueue = FCFS -> FCFS -> Event (Queue FCFS FCFS a)
forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue FCFS
FCFS FCFS
FCFS
newLCFSQueue :: Event (LCFSQueue a)
newLCFSQueue :: forall a. Event (LCFSQueue a)
newLCFSQueue = LCFS -> FCFS -> Event (Queue LCFS FCFS a)
forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue LCFS
LCFS FCFS
FCFS
newSIROQueue :: Event (SIROQueue a)
newSIROQueue :: forall a. Event (SIROQueue a)
newSIROQueue = SIRO -> FCFS -> Event (Queue SIRO FCFS a)
forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue SIRO
SIRO FCFS
FCFS
newPriorityQueue :: Event (PriorityQueue a)
newPriorityQueue :: forall a. Event (PriorityQueue a)
newPriorityQueue = StaticPriorities -> FCFS -> Event (Queue StaticPriorities FCFS a)
forall sm so a.
(QueueStrategy sm, QueueStrategy so) =>
sm -> so -> Event (Queue sm so a)
newQueue StaticPriorities
StaticPriorities FCFS
FCFS
newQueue :: (QueueStrategy sm,
QueueStrategy so) =>
sm
-> so
-> 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 <- Dynamics Double -> Event Double
forall a. Dynamics a -> Event a
forall (m :: * -> *) a. DynamicsLift m => Dynamics a -> m a
liftDynamics Dynamics Double
time
IORef Int
i <- IO (IORef Int) -> Event (IORef Int)
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef Int) -> Event (IORef Int))
-> IO (IORef Int) -> Event (IORef Int)
forall a b. (a -> b) -> a -> b
$ Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef Int
0
IORef (TimingStats Int)
is <- IO (IORef (TimingStats Int)) -> Event (IORef (TimingStats Int))
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef (TimingStats Int)) -> Event (IORef (TimingStats Int)))
-> IO (IORef (TimingStats Int)) -> Event (IORef (TimingStats Int))
forall a b. (a -> b) -> a -> b
$ TimingStats Int -> IO (IORef (TimingStats Int))
forall a. a -> IO (IORef a)
newIORef (TimingStats Int -> IO (IORef (TimingStats Int)))
-> TimingStats Int -> IO (IORef (TimingStats Int))
forall a b. (a -> b) -> a -> b
$ Double -> Int -> TimingStats Int
forall a. TimingData a => Double -> a -> TimingStats a
returnTimingStats Double
t Int
0
IORef Int
cm <- IO (IORef Int) -> Event (IORef Int)
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef Int) -> Event (IORef Int))
-> IO (IORef Int) -> Event (IORef Int)
forall a b. (a -> b) -> a -> b
$ Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef Int
0
IORef Int
cr <- IO (IORef Int) -> Event (IORef Int)
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef Int) -> Event (IORef Int))
-> IO (IORef Int) -> Event (IORef Int)
forall a b. (a -> b) -> a -> b
$ Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef Int
0
IORef Int
co <- IO (IORef Int) -> Event (IORef Int)
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef Int) -> Event (IORef Int))
-> IO (IORef Int) -> Event (IORef Int)
forall a b. (a -> b) -> a -> b
$ Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef Int
0
StrategyQueue sm (QueueItem a)
qm <- Simulation (StrategyQueue sm (QueueItem a))
-> Event (StrategyQueue sm (QueueItem a))
forall a. Simulation a -> Event a
forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation (Simulation (StrategyQueue sm (QueueItem a))
-> Event (StrategyQueue sm (QueueItem a)))
-> Simulation (StrategyQueue sm (QueueItem a))
-> Event (StrategyQueue sm (QueueItem a))
forall a b. (a -> b) -> a -> b
$ sm -> Simulation (StrategyQueue sm (QueueItem a))
forall i. sm -> Simulation (StrategyQueue sm i)
forall s i. QueueStrategy s => s -> Simulation (StrategyQueue s i)
newStrategyQueue sm
sm
Resource so
ro <- Simulation (Resource so) -> Event (Resource so)
forall a. Simulation a -> Event a
forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation (Simulation (Resource so) -> Event (Resource so))
-> Simulation (Resource so) -> Event (Resource so)
forall a b. (a -> b) -> a -> b
$ so -> Int -> Maybe Int -> Simulation (Resource so)
forall s.
QueueStrategy s =>
s -> Int -> Maybe Int -> Simulation (Resource s)
newResourceWithMaxCount so
so Int
0 Maybe Int
forall a. Maybe a
Nothing
IORef (SamplingStats Double)
w <- IO (IORef (SamplingStats Double))
-> Event (IORef (SamplingStats Double))
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef (SamplingStats Double))
-> Event (IORef (SamplingStats Double)))
-> IO (IORef (SamplingStats Double))
-> Event (IORef (SamplingStats Double))
forall a b. (a -> b) -> a -> b
$ SamplingStats Double -> IO (IORef (SamplingStats Double))
forall a. a -> IO (IORef a)
newIORef SamplingStats Double
forall a. Monoid a => a
mempty
IORef (SamplingStats Double)
wo <- IO (IORef (SamplingStats Double))
-> Event (IORef (SamplingStats Double))
forall a. IO a -> Event a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef (SamplingStats Double))
-> Event (IORef (SamplingStats Double)))
-> IO (IORef (SamplingStats Double))
-> Event (IORef (SamplingStats Double))
forall a b. (a -> b) -> a -> b
$ SamplingStats Double -> IO (IORef (SamplingStats Double))
forall a. a -> IO (IORef a)
newIORef SamplingStats Double
forall a. Monoid a => a
mempty
SignalSource a
s3 <- Simulation (SignalSource a) -> Event (SignalSource a)
forall a. Simulation a -> Event a
forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation Simulation (SignalSource a)
forall a. Simulation (SignalSource a)
newSignalSource
SignalSource ()
s4 <- Simulation (SignalSource ()) -> Event (SignalSource ())
forall a. Simulation a -> Event a
forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation Simulation (SignalSource ())
forall a. Simulation (SignalSource a)
newSignalSource
SignalSource a
s5 <- Simulation (SignalSource a) -> Event (SignalSource a)
forall a. Simulation a -> Event a
forall (m :: * -> *) a. SimulationLift m => Simulation a -> m a
liftSimulation Simulation (SignalSource a)
forall a. Simulation (SignalSource a)
newSignalSource
Queue sm so a -> Event (Queue sm so a)
forall a. a -> Event a
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 }
queueNull :: Queue sm so a -> Event Bool
queueNull :: forall sm so a. Queue sm so a -> Event Bool
queueNull Queue sm so a
q =
(Point -> IO Bool) -> Event Bool
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Bool) -> Event Bool)
-> (Point -> IO Bool) -> Event Bool
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do Int
n <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0)
queueNullChanged :: Queue sm so a -> Signal Bool
queueNullChanged :: forall sm so a. Queue sm so a -> Signal Bool
queueNullChanged Queue sm so a
q =
(() -> Event Bool) -> Signal () -> Signal Bool
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event Bool -> () -> Event Bool
forall a b. a -> b -> a
const (Event Bool -> () -> Event Bool) -> Event Bool -> () -> Event Bool
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Bool
forall sm so a. Queue sm so a -> Event Bool
queueNull Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
queueNullChanged_ Queue sm so a
q)
queueNullChanged_ :: Queue sm so a -> Signal ()
queueNullChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueNullChanged_ = Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
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 =
(Point -> IO Int) -> Event Int
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Int) -> Event Int) -> (Point -> IO Int) -> Event Int
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
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 =
(Point -> IO (TimingStats Int)) -> Event (TimingStats Int)
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO (TimingStats Int)) -> Event (TimingStats Int))
-> (Point -> IO (TimingStats Int)) -> Event (TimingStats Int)
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef (TimingStats Int) -> IO (TimingStats Int)
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef (TimingStats Int)
forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q)
queueCountChanged :: Queue sm so a -> Signal Int
queueCountChanged :: forall sm so a. Queue sm so a -> Signal Int
queueCountChanged Queue sm so a
q =
(() -> Event Int) -> Signal () -> Signal Int
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event Int -> () -> Event Int
forall a b. a -> b -> a
const (Event Int -> () -> Event Int) -> Event Int -> () -> Event Int
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
queueCount Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
queueCountChanged_ Queue sm so a
q)
queueCountChanged_ :: Queue sm so a -> Signal ()
queueCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueCountChanged_ Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q) Signal () -> Signal () -> Signal ()
forall a. Semigroup a => a -> a -> a
<>
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
enqueueStoreCount :: Queue sm so a -> Event Int
enqueueStoreCount :: forall sm so a. Queue sm so a -> Event Int
enqueueStoreCount Queue sm so a
q =
(Point -> IO Int) -> Event Int
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Int) -> Event Int) -> (Point -> IO Int) -> Event Int
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q)
enqueueStoreCountChanged :: Queue sm so a -> Signal Int
enqueueStoreCountChanged :: forall sm so a. Queue sm so a -> Signal Int
enqueueStoreCountChanged Queue sm so a
q =
(() -> Event Int) -> Signal () -> Signal Int
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event Int -> () -> Event Int
forall a b. a -> b -> a
const (Event Int -> () -> Event Int) -> Event Int -> () -> Event Int
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
enqueueStoreCount Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
enqueueStoreCountChanged_ Queue sm so a
q)
enqueueStoreCountChanged_ :: Queue sm so a -> Signal ()
enqueueStoreCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
enqueueStoreCountChanged_ Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q)
dequeueCount :: Queue sm so a -> Event Int
dequeueCount :: forall sm so a. Queue sm so a -> Event Int
dequeueCount Queue sm so a
q =
(Point -> IO Int) -> Event Int
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Int) -> Event Int) -> (Point -> IO Int) -> Event Int
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q)
dequeueCountChanged :: Queue sm so a -> Signal Int
dequeueCountChanged :: forall sm so a. Queue sm so a -> Signal Int
dequeueCountChanged Queue sm so a
q =
(() -> Event Int) -> Signal () -> Signal Int
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event Int -> () -> Event Int
forall a b. a -> b -> a
const (Event Int -> () -> Event Int) -> Event Int -> () -> Event Int
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
dequeueCount Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
dequeueCountChanged_ Queue sm so a
q)
dequeueCountChanged_ :: Queue sm so a -> Signal ()
dequeueCountChanged_ :: forall sm so a. Queue sm so a -> Signal ()
dequeueCountChanged_ Queue sm so a
q =
(() -> ()) -> Signal () -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> () -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
dequeueRequested Queue sm so a
q)
dequeueExtractCount :: Queue sm so a -> Event Int
Queue sm so a
q =
(Point -> IO Int) -> Event Int
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Int) -> Event Int) -> (Point -> IO Int) -> Event Int
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q)
dequeueExtractCountChanged :: Queue sm so a -> Signal Int
Queue sm so a
q =
(() -> Event Int) -> Signal () -> Signal Int
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event Int -> () -> Event Int
forall a b. a -> b -> a
const (Event Int -> () -> Event Int) -> Event Int -> () -> Event Int
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
dequeueExtractCount Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
dequeueExtractCountChanged_ Queue sm so a
q)
dequeueExtractCountChanged_ :: Queue sm so a -> Signal ()
Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
enqueueStoreRate :: Queue sm so a -> Event Double
enqueueStoreRate :: forall sm so a. Queue sm so a -> Event Double
enqueueStoreRate Queue sm so a
q =
(Point -> IO Double) -> Event Double
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Double) -> Event Double)
-> (Point -> IO Double) -> Event Double
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do Int
x <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q)
let t0 :: Double
t0 = Specs -> Double
spcStartTime (Specs -> Double) -> Specs -> Double
forall a b. (a -> b) -> a -> b
$ Point -> Specs
pointSpecs Point
p
t :: Double
t = Point -> Double
pointTime Point
p
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t0))
dequeueRate :: Queue sm so a -> Event Double
dequeueRate :: forall sm so a. Queue sm so a -> Event Double
dequeueRate Queue sm so a
q =
(Point -> IO Double) -> Event Double
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Double) -> Event Double)
-> (Point -> IO Double) -> Event Double
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do Int
x <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q)
let t0 :: Double
t0 = Specs -> Double
spcStartTime (Specs -> Double) -> Specs -> Double
forall a b. (a -> b) -> a -> b
$ Point -> Specs
pointSpecs Point
p
t :: Double
t = Point -> Double
pointTime Point
p
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t0))
dequeueExtractRate :: Queue sm so a -> Event Double
Queue sm so a
q =
(Point -> IO Double) -> Event Double
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Double) -> Event Double)
-> (Point -> IO Double) -> Event Double
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do Int
x <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q)
let t0 :: Double
t0 = Specs -> Double
spcStartTime (Specs -> Double) -> Specs -> Double
forall a b. (a -> b) -> a -> b
$ Point -> Specs
pointSpecs Point
p
t :: Double
t = Point -> Double
pointTime Point
p
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t0))
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 =
(Point -> IO (SamplingStats Double))
-> Event (SamplingStats Double)
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO (SamplingStats Double))
-> Event (SamplingStats Double))
-> (Point -> IO (SamplingStats Double))
-> Event (SamplingStats Double)
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef (SamplingStats Double) -> IO (SamplingStats Double)
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q)
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 =
(() -> Event (SamplingStats Double))
-> Signal () -> Signal (SamplingStats Double)
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event (SamplingStats Double) -> () -> Event (SamplingStats Double)
forall a b. a -> b -> a
const (Event (SamplingStats Double)
-> () -> Event (SamplingStats Double))
-> Event (SamplingStats Double)
-> ()
-> Event (SamplingStats Double)
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event (SamplingStats Double)
forall sm so a. Queue sm so a -> Event (SamplingStats Double)
queueWaitTime Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
queueWaitTimeChanged_ Queue sm so a
q)
queueWaitTimeChanged_ :: Queue sm so a -> Signal ()
queueWaitTimeChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueWaitTimeChanged_ Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
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 =
(Point -> IO (SamplingStats Double))
-> Event (SamplingStats Double)
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO (SamplingStats Double))
-> Event (SamplingStats Double))
-> (Point -> IO (SamplingStats Double))
-> Event (SamplingStats Double)
forall a b. (a -> b) -> a -> b
$ \Point
p -> IORef (SamplingStats Double) -> IO (SamplingStats Double)
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef Queue sm so a
q)
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 =
(() -> Event (SamplingStats Double))
-> Signal () -> Signal (SamplingStats Double)
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event (SamplingStats Double) -> () -> Event (SamplingStats Double)
forall a b. a -> b -> a
const (Event (SamplingStats Double)
-> () -> Event (SamplingStats Double))
-> Event (SamplingStats Double)
-> ()
-> Event (SamplingStats Double)
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event (SamplingStats Double)
forall sm so a. Queue sm so a -> Event (SamplingStats Double)
dequeueWaitTime Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
dequeueWaitTimeChanged_ Queue sm so a
q)
dequeueWaitTimeChanged_ :: Queue sm so a -> Signal ()
dequeueWaitTimeChanged_ :: forall sm so a. Queue sm so a -> Signal ()
dequeueWaitTimeChanged_ Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
queueRate :: Queue sm so a -> Event Double
queueRate :: forall sm so a. Queue sm so a -> Event Double
queueRate Queue sm so a
q =
(Point -> IO Double) -> Event Double
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Double) -> Event Double)
-> (Point -> IO Double) -> Event Double
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do TimingStats Int
x <- IORef (TimingStats Int) -> IO (TimingStats Int)
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef (TimingStats Int)
forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q)
SamplingStats Double
y <- IORef (SamplingStats Double) -> IO (SamplingStats Double)
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q)
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TimingStats Int -> Double
forall a. TimingData a => TimingStats a -> Double
timingStatsMean TimingStats Int
x Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ SamplingStats Double -> Double
forall a. SamplingStats a -> Double
samplingStatsMean SamplingStats Double
y)
queueRateChanged :: Queue sm so a -> Signal Double
queueRateChanged :: forall sm so a. Queue sm so a -> Signal Double
queueRateChanged Queue sm so a
q =
(() -> Event Double) -> Signal () -> Signal Double
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM (Event Double -> () -> Event Double
forall a b. a -> b -> a
const (Event Double -> () -> Event Double)
-> Event Double -> () -> Event Double
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
queueRate Queue sm so a
q) (Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
queueRateChanged_ Queue sm so a
q)
queueRateChanged_ :: Queue sm so a -> Signal ()
queueRateChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueRateChanged_ Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q) Signal () -> Signal () -> Signal ()
forall a. Semigroup a => a -> a -> a
<>
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
dequeue :: (DequeueStrategy sm,
EnqueueStrategy so)
=> Queue sm so a
-> Process a
dequeue :: forall sm so a.
(DequeueStrategy sm, EnqueueStrategy so) =>
Queue sm so a -> Process a
dequeue Queue sm so a
q =
do Double
t <- Event Double -> Process Double
forall a. Event a -> Process a
forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent (Event Double -> Process Double) -> Event Double -> Process Double
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
Resource so -> Process ()
forall s. EnqueueStrategy s => Resource s -> Process ()
requestResource (Queue sm so a -> Resource so
forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
Event a -> Process a
forall a. Event a -> Process a
forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent (Event a -> Process a) -> Event a -> Process a
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Double -> Event a
forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t
dequeueWithOutputPriority :: (DequeueStrategy sm,
PriorityQueueStrategy so po)
=> Queue sm so a
-> po
-> Process a
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 <- Event Double -> Process Double
forall a. Event a -> Process a
forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent (Event Double -> Process Double) -> Event Double -> Process Double
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
Resource so -> po -> Process ()
forall s p.
PriorityQueueStrategy s p =>
Resource s -> p -> Process ()
requestResourceWithPriority (Queue sm so a -> Resource so
forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q) po
po
Event a -> Process a
forall a. Event a -> Process a
forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent (Event a -> Process a) -> Event a -> Process a
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Double -> Event a
forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t
tryDequeue :: DequeueStrategy sm
=> Queue sm so a
-> Event (Maybe a)
tryDequeue :: forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Event (Maybe a)
tryDequeue Queue sm so a
q =
do Bool
x <- Resource so -> Event Bool
forall s. Resource s -> Event Bool
tryRequestResourceWithinEvent (Queue sm so a -> Resource so
forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
if Bool
x
then do Double
t <- Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
(a -> Maybe a) -> Event a -> Event (Maybe a)
forall a b. (a -> b) -> Event a -> Event b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just (Event a -> Event (Maybe a)) -> Event a -> Event (Maybe a)
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Double -> Event a
forall sm so a.
DequeueStrategy sm =>
Queue sm so a -> Double -> Event a
dequeueExtract Queue sm so a
q Double
t
else Maybe a -> Event (Maybe a)
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
queueDelete :: (Eq a,
DeletingQueueStrategy sm,
DequeueStrategy so)
=> Queue sm so a
-> a
-> Event Bool
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 = (Maybe a -> Bool) -> Event (Maybe a) -> Event Bool
forall a b. (a -> b) -> Event a -> Event b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Event (Maybe a) -> Event Bool) -> Event (Maybe a) -> Event Bool
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> (a -> Bool) -> Event (Maybe a)
forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueDeleteBy Queue sm so a
q (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a)
queueDelete_ :: (Eq a,
DeletingQueueStrategy sm,
DequeueStrategy so)
=> Queue sm so a
-> a
-> 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 = (Maybe a -> ()) -> Event (Maybe a) -> Event ()
forall a b. (a -> b) -> Event a -> Event b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (() -> Maybe a -> ()
forall a b. a -> b -> a
const ()) (Event (Maybe a) -> Event ()) -> Event (Maybe a) -> Event ()
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> (a -> Bool) -> Event (Maybe a)
forall sm so a.
(DeletingQueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueDeleteBy Queue sm so a
q (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a)
queueDeleteBy :: (DeletingQueueStrategy sm,
DequeueStrategy so)
=> Queue sm so a
-> (a -> Bool)
-> 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 <- Resource so -> Event Bool
forall s. Resource s -> Event Bool
tryRequestResourceWithinEvent (Queue sm so a -> Resource so
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 <- StrategyQueue sm (QueueItem a)
-> (QueueItem a -> Bool) -> Event (Maybe (QueueItem a))
forall s i.
DeletingQueueStrategy s =>
StrategyQueue s i -> (i -> Bool) -> Event (Maybe i)
forall i. StrategyQueue sm i -> (i -> Bool) -> Event (Maybe i)
strategyQueueDeleteBy (Queue sm so a -> StrategyQueue sm (QueueItem a)
forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) (a -> Bool
pred (a -> Bool) -> (QueueItem a -> a) -> QueueItem a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueueItem a -> a
forall a. QueueItem a -> a
itemValue)
case Maybe (QueueItem a)
i of
Maybe (QueueItem a)
Nothing ->
do Resource so -> Event ()
forall s. DequeueStrategy s => Resource s -> Event ()
releaseResourceWithinEvent (Queue sm so a -> Resource so
forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
Maybe a -> Event (Maybe a)
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
Just QueueItem a
i ->
do Double
t <- Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q
(a -> Maybe a) -> Event a -> Event (Maybe a)
forall a b. (a -> b) -> Event a -> Event b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just (Event a -> Event (Maybe a)) -> Event a -> Event (Maybe a)
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> Double -> QueueItem a -> Event a
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 Maybe a -> Event (Maybe a)
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
queueDeleteBy_ :: (DeletingQueueStrategy sm,
DequeueStrategy so)
=> Queue sm so a
-> (a -> Bool)
-> 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 = (Maybe a -> ()) -> Event (Maybe a) -> Event ()
forall a b. (a -> b) -> Event a -> Event b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (() -> Maybe a -> ()
forall a b. a -> b -> a
const ()) (Event (Maybe a) -> Event ()) -> Event (Maybe a) -> Event ()
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> (a -> Bool) -> Event (Maybe a)
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
queueContains :: (Eq a,
DeletingQueueStrategy sm)
=> Queue sm so a
-> a
-> Event Bool
queueContains :: forall a sm so.
(Eq a, DeletingQueueStrategy sm) =>
Queue sm so a -> a -> Event Bool
queueContains Queue sm so a
q a
a = (Maybe a -> Bool) -> Event (Maybe a) -> Event Bool
forall a b. (a -> b) -> Event a -> Event b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Event (Maybe a) -> Event Bool) -> Event (Maybe a) -> Event Bool
forall a b. (a -> b) -> a -> b
$ Queue sm so a -> (a -> Bool) -> Event (Maybe a)
forall sm so a.
DeletingQueueStrategy sm =>
Queue sm so a -> (a -> Bool) -> Event (Maybe a)
queueContainsBy Queue sm so a
q (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a)
queueContainsBy :: DeletingQueueStrategy sm
=> Queue sm so a
-> (a -> Bool)
-> Event (Maybe a)
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 <- StrategyQueue sm (QueueItem a)
-> (QueueItem a -> Bool) -> Event (Maybe (QueueItem a))
forall s i.
DeletingQueueStrategy s =>
StrategyQueue s i -> (i -> Bool) -> Event (Maybe i)
forall i. StrategyQueue sm i -> (i -> Bool) -> Event (Maybe i)
strategyQueueContainsBy (Queue sm so a -> StrategyQueue sm (QueueItem a)
forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) (a -> Bool
pred (a -> Bool) -> (QueueItem a -> a) -> QueueItem a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueueItem a -> a
forall a. QueueItem a -> a
itemValue)
case Maybe (QueueItem a)
x of
Maybe (QueueItem a)
Nothing -> Maybe a -> Event (Maybe a)
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
Just QueueItem a
i -> Maybe a -> Event (Maybe a)
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a -> Event (Maybe a)) -> Maybe a -> Event (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just (QueueItem a -> a
forall a. QueueItem a -> a
itemValue QueueItem a
i)
clearQueue :: DequeueStrategy sm
=> Queue sm so a
-> Event ()
clearQueue :: forall sm so a. DequeueStrategy sm => Queue sm so a -> Event ()
clearQueue Queue sm so a
q =
do Maybe a
x <- Queue sm so a -> Event (Maybe a)
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 -> () -> Event ()
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just a
a -> Queue sm so a -> Event ()
forall sm so a. DequeueStrategy sm => Queue sm so a -> Event ()
clearQueue Queue sm so a
q
enqueue :: (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 ()
enqueue = Queue sm so a -> a -> Event ()
forall sm so a.
(EnqueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event ()
enqueueStore
enqueueWithStoringPriority :: (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 ()
enqueueWithStoringPriority = Queue sm so a -> pm -> a -> Event ()
forall sm pm so a.
(PriorityQueueStrategy sm pm, DequeueStrategy so) =>
Queue sm so a -> pm -> a -> Event ()
enqueueStoreWithPriority
enqueueStored :: Queue sm so a -> Signal a
enqueueStored :: forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q = SignalSource a -> Signal a
forall a. SignalSource a -> Signal a
publishSignal (Queue sm so a -> SignalSource a
forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource Queue sm so a
q)
dequeueRequested :: Queue sm so a -> Signal ()
dequeueRequested :: forall sm so a. Queue sm so a -> Signal ()
dequeueRequested Queue sm so a
q = SignalSource () -> Signal ()
forall a. SignalSource a -> Signal a
publishSignal (Queue sm so a -> SignalSource ()
forall sm so a. Queue sm so a -> SignalSource ()
dequeueRequestedSource Queue sm so a
q)
dequeueExtracted :: Queue sm so a -> Signal a
Queue sm so a
q = SignalSource a -> Signal a
forall a. SignalSource a -> Signal a
publishSignal (Queue sm so a -> SignalSource a
forall sm so a. Queue sm so a -> SignalSource a
dequeueExtractedSource Queue sm so a
q)
enqueueStore :: (EnqueueStrategy sm,
DequeueStrategy so)
=> Queue sm so a
-> a
-> Event ()
enqueueStore :: forall sm so a.
(EnqueueStrategy sm, DequeueStrategy so) =>
Queue sm so a -> a -> Event ()
enqueueStore Queue sm so a
q a
a =
(Point -> IO ()) -> Event ()
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO ()) -> Event ()) -> (Point -> IO ()) -> 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 }
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
StrategyQueue sm (QueueItem a) -> QueueItem a -> Event ()
forall s i. EnqueueStrategy s => StrategyQueue s i -> i -> Event ()
forall i. StrategyQueue sm i -> i -> Event ()
strategyEnqueue (Queue sm so a -> StrategyQueue sm (QueueItem a)
forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q) QueueItem a
i
Int
c <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
let c' :: Int
c' = Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
t :: Double
t = Point -> Double
pointTime Point
p
Int
c' Int -> IO () -> IO ()
forall a b. a -> b -> b
`seq` IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q) Int
c'
IORef (TimingStats Int)
-> (TimingStats Int -> TimingStats Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef (TimingStats Int)
forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (Double -> Int -> TimingStats Int -> TimingStats Int
forall a.
TimingData a =>
Double -> a -> TimingStats a -> TimingStats a
addTimingStats Double
t Int
c')
IORef Int -> (Int -> Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
Resource so -> Event ()
forall s. DequeueStrategy s => Resource s -> Event ()
releaseResourceWithinEvent (Queue sm so a -> Resource so
forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
SignalSource a -> a -> Event ()
forall a. SignalSource a -> a -> Event ()
triggerSignal (Queue sm so a -> SignalSource a
forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource Queue sm so a
q) (QueueItem a -> a
forall a. QueueItem a -> a
itemValue QueueItem a
i)
enqueueStoreWithPriority :: (PriorityQueueStrategy sm pm,
DequeueStrategy so)
=> Queue sm so a
-> pm
-> a
-> 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 =
(Point -> IO ()) -> Event ()
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO ()) -> Event ()) -> (Point -> IO ()) -> 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 }
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
StrategyQueue sm (QueueItem a) -> pm -> QueueItem a -> Event ()
forall i. StrategyQueue sm i -> pm -> i -> Event ()
forall s p i.
PriorityQueueStrategy s p =>
StrategyQueue s i -> p -> i -> Event ()
strategyEnqueueWithPriority (Queue sm so a -> StrategyQueue sm (QueueItem a)
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 <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
let c' :: Int
c' = Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
t :: Double
t = Point -> Double
pointTime Point
p
Int
c' Int -> IO () -> IO ()
forall a b. a -> b -> b
`seq` IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q) Int
c'
IORef (TimingStats Int)
-> (TimingStats Int -> TimingStats Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef (TimingStats Int)
forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (Double -> Int -> TimingStats Int -> TimingStats Int
forall a.
TimingData a =>
Double -> a -> TimingStats a -> TimingStats a
addTimingStats Double
t Int
c')
IORef Int -> (Int -> Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
Resource so -> Event ()
forall s. DequeueStrategy s => Resource s -> Event ()
releaseResourceWithinEvent (Queue sm so a -> Resource so
forall sm so a. Queue sm so a -> Resource so
dequeueRes Queue sm so a
q)
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
SignalSource a -> a -> Event ()
forall a. SignalSource a -> a -> Event ()
triggerSignal (Queue sm so a -> SignalSource a
forall sm so a. Queue sm so a -> SignalSource a
enqueueStoredSource Queue sm so a
q) (QueueItem a -> a
forall a. QueueItem a -> a
itemValue QueueItem a
i)
dequeueRequest :: Queue sm so a
-> Event Double
dequeueRequest :: forall sm so a. Queue sm so a -> Event Double
dequeueRequest Queue sm so a
q =
(Point -> IO Double) -> Event Double
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO Double) -> Event Double)
-> (Point -> IO Double) -> Event Double
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do IORef Int -> (Int -> Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
SignalSource () -> () -> Event ()
forall a. SignalSource a -> a -> Event ()
triggerSignal (Queue sm so a -> SignalSource ()
forall sm so a. Queue sm so a -> SignalSource ()
dequeueRequestedSource Queue sm so a
q) ()
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Double -> IO Double) -> Double -> IO Double
forall a b. (a -> b) -> a -> b
$ Point -> Double
pointTime Point
p
dequeueExtract :: DequeueStrategy sm
=> Queue sm so a
-> Double
-> Event a
Queue sm so a
q Double
t' =
(Point -> IO a) -> Event a
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO a) -> Event a) -> (Point -> IO a) -> Event a
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do QueueItem a
i <- Point -> Event (QueueItem a) -> IO (QueueItem a)
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event (QueueItem a) -> IO (QueueItem a))
-> Event (QueueItem a) -> IO (QueueItem a)
forall a b. (a -> b) -> a -> b
$
StrategyQueue sm (QueueItem a) -> Event (QueueItem a)
forall s i. DequeueStrategy s => StrategyQueue s i -> Event i
forall i. StrategyQueue sm i -> Event i
strategyDequeue (Queue sm so a -> StrategyQueue sm (QueueItem a)
forall sm so a. Queue sm so a -> StrategyQueue sm (QueueItem a)
queueStore Queue sm so a
q)
Point -> Event a -> IO a
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event a -> IO a) -> Event a -> IO a
forall a b. (a -> b) -> a -> b
$
Queue sm so a -> Double -> QueueItem a -> Event a
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
dequeuePostExtract :: DequeueStrategy sm
=> Queue sm so a
-> Double
-> QueueItem a
-> Event a
Queue sm so a
q Double
t' QueueItem a
i =
(Point -> IO a) -> Event a
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO a) -> Event a) -> (Point -> IO a) -> Event a
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do Int
c <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
let c' :: Int
c' = Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
t :: Double
t = Point -> Double
pointTime Point
p
Int
c' Int -> IO () -> IO ()
forall a b. a -> b -> b
`seq` IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q) Int
c'
IORef (TimingStats Int)
-> (TimingStats Int -> TimingStats Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef (TimingStats Int)
forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (Double -> Int -> TimingStats Int -> TimingStats Int
forall a.
TimingData a =>
Double -> a -> TimingStats a -> TimingStats a
addTimingStats Double
t Int
c')
IORef Int -> (Int -> Int) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
Queue sm so a -> Double -> QueueItem a -> Event ()
forall sm so a. Queue sm so a -> Double -> QueueItem a -> Event ()
dequeueStat Queue sm so a
q Double
t' QueueItem a
i
Point -> Event () -> IO ()
forall a. Point -> Event a -> IO a
invokeEvent Point
p (Event () -> IO ()) -> Event () -> IO ()
forall a b. (a -> b) -> a -> b
$
SignalSource a -> a -> Event ()
forall a. SignalSource a -> a -> Event ()
triggerSignal (Queue sm so a -> SignalSource a
forall sm so a. Queue sm so a -> SignalSource a
dequeueExtractedSource Queue sm so a
q) (QueueItem a -> a
forall a. QueueItem a -> a
itemValue QueueItem a
i)
a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> IO a) -> a -> IO a
forall a b. (a -> b) -> a -> b
$ QueueItem a -> a
forall a. QueueItem a -> a
itemValue QueueItem a
i
dequeueStat :: Queue sm so a
-> Double
-> QueueItem a
-> Event ()
dequeueStat :: forall sm so a. Queue sm so a -> Double -> QueueItem a -> Event ()
dequeueStat Queue sm so a
q Double
t' QueueItem a
i =
(Point -> IO ()) -> Event ()
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO ()) -> Event ()) -> (Point -> IO ()) -> Event ()
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do let t1 :: Double
t1 = QueueItem a -> Double
forall a. QueueItem a -> Double
itemStoringTime QueueItem a
i
t :: Double
t = Point -> Double
pointTime Point
p
IORef (SamplingStats Double)
-> (SamplingStats Double -> SamplingStats Double) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef Queue sm so a
q) ((SamplingStats Double -> SamplingStats Double) -> IO ())
-> (SamplingStats Double -> SamplingStats Double) -> IO ()
forall a b. (a -> b) -> a -> b
$
Double -> SamplingStats Double -> SamplingStats Double
forall a. SamplingData a => a -> SamplingStats a -> SamplingStats a
addSamplingStats (Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t')
IORef (SamplingStats Double)
-> (SamplingStats Double -> SamplingStats Double) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q) ((SamplingStats Double -> SamplingStats Double) -> IO ())
-> (SamplingStats Double -> SamplingStats Double) -> IO ()
forall a b. (a -> b) -> a -> b
$
Double -> SamplingStats Double -> SamplingStats Double
forall a. SamplingData a => a -> SamplingStats a -> SamplingStats a
addSamplingStats (Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t1)
queueChanged_ :: Queue sm so a -> Signal ()
queueChanged_ :: forall sm so a. Queue sm so a -> Signal ()
queueChanged_ Queue sm so a
q =
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
enqueueStored Queue sm so a
q) Signal () -> Signal () -> Signal ()
forall a. Semigroup a => a -> a -> a
<>
Queue sm so a -> Signal ()
forall sm so a. Queue sm so a -> Signal ()
dequeueRequested Queue sm so a
q Signal () -> Signal () -> Signal ()
forall a. Semigroup a => a -> a -> a
<>
(a -> ()) -> Signal a -> Signal ()
forall a b. (a -> b) -> Signal a -> Signal b
mapSignal (() -> a -> ()
forall a b. a -> b -> a
const ()) (Queue sm so a -> Signal a
forall sm so a. Queue sm so a -> Signal a
dequeueExtracted Queue sm so a
q)
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 = Queue sm so a -> sm
forall sm so a. Queue sm so a -> sm
enqueueStoringStrategy Queue sm so a
q
so :: so
so = Queue sm so a -> so
forall sm so a. Queue sm so a -> so
dequeueStrategy Queue sm so a
q
Bool
null <- Queue sm so a -> Event Bool
forall sm so a. Queue sm so a -> Event Bool
queueNull Queue sm so a
q
Int
count <- Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
queueCount Queue sm so a
q
TimingStats Int
countStats <- Queue sm so a -> Event (TimingStats Int)
forall sm so a. Queue sm so a -> Event (TimingStats Int)
queueCountStats Queue sm so a
q
Int
enqueueStoreCount <- Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
enqueueStoreCount Queue sm so a
q
Int
dequeueCount <- Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
dequeueCount Queue sm so a
q
Int
dequeueExtractCount <- Queue sm so a -> Event Int
forall sm so a. Queue sm so a -> Event Int
dequeueExtractCount Queue sm so a
q
Double
enqueueStoreRate <- Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
enqueueStoreRate Queue sm so a
q
Double
dequeueRate <- Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
dequeueRate Queue sm so a
q
Double
dequeueExtractRate <- Queue sm so a -> Event Double
forall sm so a. Queue sm so a -> Event Double
dequeueExtractRate Queue sm so a
q
SamplingStats Double
waitTime <- Queue sm so a -> Event (SamplingStats Double)
forall sm so a. Queue sm so a -> Event (SamplingStats Double)
queueWaitTime Queue sm so a
q
SamplingStats Double
dequeueWaitTime <- Queue sm so a -> Event (SamplingStats Double)
forall sm so a. Queue sm so a -> Event (SamplingStats Double)
dequeueWaitTime Queue sm so a
q
let tab :: [Char]
tab = Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
ShowS -> Event ShowS
forall a. a -> Event a
forall (m :: * -> *) a. Monad m => a -> m a
return (ShowS -> Event ShowS) -> ShowS -> Event ShowS
forall a b. (a -> b) -> a -> b
$
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"the storing (memory) strategy = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
sm -> ShowS
forall a. Show a => a -> ShowS
shows sm
sm ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"the dequeueing (output) strategy = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
so -> ShowS
forall a. Show a => a -> ShowS
shows so
so ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"empty? = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> ShowS
forall a. Show a => a -> ShowS
shows Bool
null ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"the current size = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
count ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"the size statistics = \n\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
TimingStats Int -> Int -> ShowS
forall a. (Show a, TimingData a) => TimingStats a -> Int -> ShowS
timingStatsSummary TimingStats Int
countStats (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
indent) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
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) = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
enqueueStoreCount ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"the dequeue count (number of requests for dequeueing an item) = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
dequeueCount ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
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) = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
dequeueExtractCount ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
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) = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Double -> ShowS
forall a. Show a => a -> ShowS
shows Double
enqueueStoreRate ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"the dequeue rate (how many requests for dequeueing per time) = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Double -> ShowS
forall a. Show a => a -> ShowS
shows Double
dequeueRate ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
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) = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Double -> ShowS
forall a. Show a => a -> ShowS
shows Double
dequeueExtractRate ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
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" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
SamplingStats Double -> Int -> ShowS
forall a. Show a => SamplingStats a -> Int -> ShowS
samplingStatsSummary SamplingStats Double
waitTime (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
indent) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
"\n\n" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> ShowS
showString [Char]
tab ShowS -> ShowS -> ShowS
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" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
SamplingStats Double -> Int -> ShowS
forall a. Show a => SamplingStats a -> Int -> ShowS
samplingStatsSummary SamplingStats Double
dequeueWaitTime (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
indent)
resetQueue :: Queue sm so a -> Event ()
resetQueue :: forall sm so a. Queue sm so a -> Event ()
resetQueue Queue sm so a
q =
(Point -> IO ()) -> Event ()
forall a. (Point -> IO a) -> Event a
Event ((Point -> IO ()) -> Event ()) -> (Point -> IO ()) -> Event ()
forall a b. (a -> b) -> a -> b
$ \Point
p ->
do let t :: Double
t = Point -> Double
pointTime Point
p
Int
queueCount <- IORef Int -> IO Int
forall a. IORef a -> IO a
readIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
queueCountRef Queue sm so a
q)
IORef (TimingStats Int) -> TimingStats Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef (TimingStats Int)
forall sm so a. Queue sm so a -> IORef (TimingStats Int)
queueCountStatsRef Queue sm so a
q) (TimingStats Int -> IO ()) -> TimingStats Int -> IO ()
forall a b. (a -> b) -> a -> b
$
Double -> Int -> TimingStats Int
forall a. TimingData a => Double -> a -> TimingStats a
returnTimingStats Double
t Int
queueCount
IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
enqueueStoreCountRef Queue sm so a
q) Int
0
IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueCountRef Queue sm so a
q) Int
0
IORef Int -> Int -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef Int
forall sm so a. Queue sm so a -> IORef Int
dequeueExtractCountRef Queue sm so a
q) Int
0
IORef (SamplingStats Double) -> SamplingStats Double -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
queueWaitTimeRef Queue sm so a
q) SamplingStats Double
forall a. Monoid a => a
mempty
IORef (SamplingStats Double) -> SamplingStats Double -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (Queue sm so a -> IORef (SamplingStats Double)
forall sm so a. Queue sm so a -> IORef (SamplingStats Double)
dequeueWaitTimeRef Queue sm so a
q) SamplingStats Double
forall a. Monoid a => a
mempty