aivika-transformers-4.6: Transformers for the Aivika simulation library

CopyrightCopyright (c) 2009-2016 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Simulation.Aivika.Trans.QueueStrategy

Description

Tested with: GHC 8.0.1

This module defines the queue strategies.

Synopsis

Documentation

class Monad m => QueueStrategy m s where Source #

Defines the basic queue strategy.

Minimal complete definition

newStrategyQueue, strategyQueueNull

Associated Types

data StrategyQueue m s :: * -> * Source #

The strategy queue.

Methods

newStrategyQueue :: s -> Simulation m (StrategyQueue m s a) Source #

Create a new queue by the specified strategy.

strategyQueueNull :: StrategyQueue m s a -> Event m Bool Source #

Test whether the queue is empty.

class QueueStrategy m s => DequeueStrategy m s where Source #

Defines a strategy with support of the dequeuing operation.

Minimal complete definition

strategyDequeue

Methods

strategyDequeue :: StrategyQueue m s a -> Event m a Source #

Dequeue the front element and return it.

class DequeueStrategy m s => EnqueueStrategy m s where Source #

It defines a strategy when we can enqueue a single element.

Minimal complete definition

strategyEnqueue

Methods

strategyEnqueue :: StrategyQueue m s a -> a -> Event m () Source #

Enqueue an element.

class DequeueStrategy m s => PriorityQueueStrategy m s p | s -> p where Source #

It defines a strategy when we can enqueue an element with the specified priority.

Minimal complete definition

strategyEnqueueWithPriority

Methods

strategyEnqueueWithPriority :: StrategyQueue m s a -> p -> a -> Event m () Source #

Enqueue an element with the specified priority.

class DequeueStrategy m s => DeletingQueueStrategy m s where Source #

Defines a strategy with support of the deleting operation.

Methods

strategyQueueDelete :: Eq a => StrategyQueue m s a -> a -> Event m Bool Source #

Remove the element and return a flag indicating whether the element was found and removed.

strategyQueueDeleteBy :: StrategyQueue m s a -> (a -> Bool) -> Event m (Maybe a) Source #

Remove an element satisfying the predicate and return the element if found.

strategyQueueContains :: Eq a => StrategyQueue m s a -> a -> Event m Bool Source #

Detect whether the specified element is contained in the queue.

strategyQueueContainsBy :: StrategyQueue m s a -> (a -> Bool) -> Event m (Maybe a) Source #

Detect whether an element satifying the specified predicate is contained in the queue.

data FCFS Source #

Strategy: First Come - First Served (FCFS).

Constructors

FCFS 

Instances

Eq FCFS Source # 

Methods

(==) :: FCFS -> FCFS -> Bool #

(/=) :: FCFS -> FCFS -> Bool #

Ord FCFS Source # 

Methods

compare :: FCFS -> FCFS -> Ordering #

(<) :: FCFS -> FCFS -> Bool #

(<=) :: FCFS -> FCFS -> Bool #

(>) :: FCFS -> FCFS -> Bool #

(>=) :: FCFS -> FCFS -> Bool #

max :: FCFS -> FCFS -> FCFS #

min :: FCFS -> FCFS -> FCFS #

Show FCFS Source # 

Methods

showsPrec :: Int -> FCFS -> ShowS #

show :: FCFS -> String #

showList :: [FCFS] -> ShowS #

ResultItemable (ResultValue FCFS) Source # 
data StrategyQueue IO FCFS Source # 

data LCFS Source #

Strategy: Last Come - First Served (LCFS)

Constructors

LCFS 

Instances

Eq LCFS Source # 

Methods

(==) :: LCFS -> LCFS -> Bool #

(/=) :: LCFS -> LCFS -> Bool #

Ord LCFS Source # 

Methods

compare :: LCFS -> LCFS -> Ordering #

(<) :: LCFS -> LCFS -> Bool #

(<=) :: LCFS -> LCFS -> Bool #

(>) :: LCFS -> LCFS -> Bool #

(>=) :: LCFS -> LCFS -> Bool #

max :: LCFS -> LCFS -> LCFS #

min :: LCFS -> LCFS -> LCFS #

Show LCFS Source # 

Methods

showsPrec :: Int -> LCFS -> ShowS #

show :: LCFS -> String #

showList :: [LCFS] -> ShowS #

ResultItemable (ResultValue LCFS) Source # 
data StrategyQueue IO LCFS Source # 

data SIRO Source #

Strategy: Service in Random Order (SIRO).

Constructors

SIRO 

Instances

Eq SIRO Source # 

Methods

(==) :: SIRO -> SIRO -> Bool #

(/=) :: SIRO -> SIRO -> Bool #

Ord SIRO Source # 

Methods

compare :: SIRO -> SIRO -> Ordering #

(<) :: SIRO -> SIRO -> Bool #

(<=) :: SIRO -> SIRO -> Bool #

(>) :: SIRO -> SIRO -> Bool #

(>=) :: SIRO -> SIRO -> Bool #

max :: SIRO -> SIRO -> SIRO #

min :: SIRO -> SIRO -> SIRO #

Show SIRO Source # 

Methods

showsPrec :: Int -> SIRO -> ShowS #

show :: SIRO -> String #

showList :: [SIRO] -> ShowS #

ResultItemable (ResultValue SIRO) Source # 
data StrategyQueue IO SIRO Source # 

data StaticPriorities Source #

Strategy: Static Priorities. It uses the priority queue.

Constructors

StaticPriorities 

Instances

Eq StaticPriorities Source # 
Ord StaticPriorities Source # 
Show StaticPriorities Source # 
ResultItemable (ResultValue StaticPriorities) Source # 

Methods

resultItemName :: ResultValue StaticPriorities m -> ResultName Source #

resultItemId :: ResultValue StaticPriorities m -> ResultId Source #

resultItemSignal :: MonadDES m => ResultValue StaticPriorities m -> ResultSignal m Source #

resultItemExpansion :: MonadDES m => ResultValue StaticPriorities m -> ResultSource m Source #

resultItemSummary :: MonadDES m => ResultValue StaticPriorities m -> ResultSource m Source #

resultItemAsIntValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue Int m) Source #

resultItemAsIntListValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue [Int] m) Source #

resultItemAsIntStatsValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue (SamplingStats Int) m) Source #

resultItemAsIntTimingStatsValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue (TimingStats Int) m) Source #

resultItemAsDoubleValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue Double m) Source #

resultItemAsDoubleListValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue [Double] m) Source #

resultItemAsDoubleStatsValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue (SamplingStats Double) m) Source #

resultItemAsDoubleTimingStatsValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue (TimingStats Double) m) Source #

resultItemAsStringValue :: MonadDES m => ResultValue StaticPriorities m -> Maybe (ResultValue String m) Source #

data StrategyQueue IO StaticPriorities Source #