{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, FunctionalDependencies, UndecidableInstances #-}
module Simulation.Aivika.Trans.QueueStrategy where
import Control.Monad
import Data.Maybe
import Simulation.Aivika.Trans.Internal.Types
class Monad m => QueueStrategy m s where
data StrategyQueue m s :: * -> *
newStrategyQueue :: s
-> Simulation m (StrategyQueue m s a)
strategyQueueNull :: StrategyQueue m s a
-> Event m Bool
class QueueStrategy m s => DequeueStrategy m s where
strategyDequeue :: StrategyQueue m s a
-> Event m a
class DequeueStrategy m s => EnqueueStrategy m s where
strategyEnqueue :: StrategyQueue m s a
-> a
-> Event m ()
class DequeueStrategy m s => PriorityQueueStrategy m s p | s -> p where
strategyEnqueueWithPriority :: StrategyQueue m s a
-> p
-> a
-> Event m ()
class DequeueStrategy m s => DeletingQueueStrategy m s where
strategyQueueDelete :: Eq a
=> StrategyQueue m s a
-> a
-> Event m Bool
strategyQueueDelete StrategyQueue m s a
s a
a =
forall (m :: * -> *) a. (Point m -> m a) -> Event m a
Event forall a b. (a -> b) -> a -> b
$ \Point m
p ->
do Maybe a
x <- forall (m :: * -> *) a. Point m -> Event m a -> m a
invokeEvent Point m
p forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s a.
DeletingQueueStrategy m s =>
StrategyQueue m s a -> (a -> Bool) -> Event m (Maybe a)
strategyQueueDeleteBy StrategyQueue m s a
s (forall a. Eq a => a -> a -> Bool
== a
a)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Maybe a -> Bool
isJust Maybe a
x)
strategyQueueDeleteBy :: StrategyQueue m s a
-> (a -> Bool)
-> Event m (Maybe a)
strategyQueueContains :: Eq a
=> StrategyQueue m s a
-> a
-> Event m Bool
strategyQueueContains StrategyQueue m s a
s a
a =
forall (m :: * -> *) a. (Point m -> m a) -> Event m a
Event forall a b. (a -> b) -> a -> b
$ \Point m
p ->
do Maybe a
x <- forall (m :: * -> *) a. Point m -> Event m a -> m a
invokeEvent Point m
p forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s a.
DeletingQueueStrategy m s =>
StrategyQueue m s a -> (a -> Bool) -> Event m (Maybe a)
strategyQueueContainsBy StrategyQueue m s a
s (forall a. Eq a => a -> a -> Bool
== a
a)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Maybe a -> Bool
isJust Maybe a
x)
strategyQueueContainsBy :: StrategyQueue m s a
-> (a -> Bool)
-> Event m (Maybe a)
data FCFS = FCFS deriving (FCFS -> FCFS -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FCFS -> FCFS -> Bool
$c/= :: FCFS -> FCFS -> Bool
== :: FCFS -> FCFS -> Bool
$c== :: FCFS -> FCFS -> Bool
Eq, Eq FCFS
FCFS -> FCFS -> Bool
FCFS -> FCFS -> Ordering
FCFS -> FCFS -> FCFS
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FCFS -> FCFS -> FCFS
$cmin :: FCFS -> FCFS -> FCFS
max :: FCFS -> FCFS -> FCFS
$cmax :: FCFS -> FCFS -> FCFS
>= :: FCFS -> FCFS -> Bool
$c>= :: FCFS -> FCFS -> Bool
> :: FCFS -> FCFS -> Bool
$c> :: FCFS -> FCFS -> Bool
<= :: FCFS -> FCFS -> Bool
$c<= :: FCFS -> FCFS -> Bool
< :: FCFS -> FCFS -> Bool
$c< :: FCFS -> FCFS -> Bool
compare :: FCFS -> FCFS -> Ordering
$ccompare :: FCFS -> FCFS -> Ordering
Ord, Int -> FCFS -> ShowS
[FCFS] -> ShowS
FCFS -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FCFS] -> ShowS
$cshowList :: [FCFS] -> ShowS
show :: FCFS -> String
$cshow :: FCFS -> String
showsPrec :: Int -> FCFS -> ShowS
$cshowsPrec :: Int -> FCFS -> ShowS
Show)
data LCFS = LCFS deriving (LCFS -> LCFS -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LCFS -> LCFS -> Bool
$c/= :: LCFS -> LCFS -> Bool
== :: LCFS -> LCFS -> Bool
$c== :: LCFS -> LCFS -> Bool
Eq, Eq LCFS
LCFS -> LCFS -> Bool
LCFS -> LCFS -> Ordering
LCFS -> LCFS -> LCFS
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LCFS -> LCFS -> LCFS
$cmin :: LCFS -> LCFS -> LCFS
max :: LCFS -> LCFS -> LCFS
$cmax :: LCFS -> LCFS -> LCFS
>= :: LCFS -> LCFS -> Bool
$c>= :: LCFS -> LCFS -> Bool
> :: LCFS -> LCFS -> Bool
$c> :: LCFS -> LCFS -> Bool
<= :: LCFS -> LCFS -> Bool
$c<= :: LCFS -> LCFS -> Bool
< :: LCFS -> LCFS -> Bool
$c< :: LCFS -> LCFS -> Bool
compare :: LCFS -> LCFS -> Ordering
$ccompare :: LCFS -> LCFS -> Ordering
Ord, Int -> LCFS -> ShowS
[LCFS] -> ShowS
LCFS -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LCFS] -> ShowS
$cshowList :: [LCFS] -> ShowS
show :: LCFS -> String
$cshow :: LCFS -> String
showsPrec :: Int -> LCFS -> ShowS
$cshowsPrec :: Int -> LCFS -> ShowS
Show)
data SIRO = SIRO deriving (SIRO -> SIRO -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SIRO -> SIRO -> Bool
$c/= :: SIRO -> SIRO -> Bool
== :: SIRO -> SIRO -> Bool
$c== :: SIRO -> SIRO -> Bool
Eq, Eq SIRO
SIRO -> SIRO -> Bool
SIRO -> SIRO -> Ordering
SIRO -> SIRO -> SIRO
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SIRO -> SIRO -> SIRO
$cmin :: SIRO -> SIRO -> SIRO
max :: SIRO -> SIRO -> SIRO
$cmax :: SIRO -> SIRO -> SIRO
>= :: SIRO -> SIRO -> Bool
$c>= :: SIRO -> SIRO -> Bool
> :: SIRO -> SIRO -> Bool
$c> :: SIRO -> SIRO -> Bool
<= :: SIRO -> SIRO -> Bool
$c<= :: SIRO -> SIRO -> Bool
< :: SIRO -> SIRO -> Bool
$c< :: SIRO -> SIRO -> Bool
compare :: SIRO -> SIRO -> Ordering
$ccompare :: SIRO -> SIRO -> Ordering
Ord, Int -> SIRO -> ShowS
[SIRO] -> ShowS
SIRO -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SIRO] -> ShowS
$cshowList :: [SIRO] -> ShowS
show :: SIRO -> String
$cshow :: SIRO -> String
showsPrec :: Int -> SIRO -> ShowS
$cshowsPrec :: Int -> SIRO -> ShowS
Show)
data StaticPriorities = StaticPriorities deriving (StaticPriorities -> StaticPriorities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StaticPriorities -> StaticPriorities -> Bool
$c/= :: StaticPriorities -> StaticPriorities -> Bool
== :: StaticPriorities -> StaticPriorities -> Bool
$c== :: StaticPriorities -> StaticPriorities -> Bool
Eq, Eq StaticPriorities
StaticPriorities -> StaticPriorities -> Bool
StaticPriorities -> StaticPriorities -> Ordering
StaticPriorities -> StaticPriorities -> StaticPriorities
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StaticPriorities -> StaticPriorities -> StaticPriorities
$cmin :: StaticPriorities -> StaticPriorities -> StaticPriorities
max :: StaticPriorities -> StaticPriorities -> StaticPriorities
$cmax :: StaticPriorities -> StaticPriorities -> StaticPriorities
>= :: StaticPriorities -> StaticPriorities -> Bool
$c>= :: StaticPriorities -> StaticPriorities -> Bool
> :: StaticPriorities -> StaticPriorities -> Bool
$c> :: StaticPriorities -> StaticPriorities -> Bool
<= :: StaticPriorities -> StaticPriorities -> Bool
$c<= :: StaticPriorities -> StaticPriorities -> Bool
< :: StaticPriorities -> StaticPriorities -> Bool
$c< :: StaticPriorities -> StaticPriorities -> Bool
compare :: StaticPriorities -> StaticPriorities -> Ordering
$ccompare :: StaticPriorities -> StaticPriorities -> Ordering
Ord, Int -> StaticPriorities -> ShowS
[StaticPriorities] -> ShowS
StaticPriorities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StaticPriorities] -> ShowS
$cshowList :: [StaticPriorities] -> ShowS
show :: StaticPriorities -> String
$cshow :: StaticPriorities -> String
showsPrec :: Int -> StaticPriorities -> ShowS
$cshowsPrec :: Int -> StaticPriorities -> ShowS
Show)