module Simulation.Aivika.Trans.GPSS.AssemblySet
(
AssemblySet,
newAssemblySet,
assembleTransact,
gatherTransacts,
transactAssembling,
transactGathering) where
import Data.Monoid
import Data.Maybe
import Data.Hashable
import Control.Monad
import Control.Monad.Trans
import Simulation.Aivika.Trans
import Simulation.Aivika.Trans.Internal.Specs
import Simulation.Aivika.Trans.Internal.Parameter
import Simulation.Aivika.Trans.Internal.Simulation
import Simulation.Aivika.Trans.GPSS.Transact
import Simulation.Aivika.Trans.GPSS.TransactQueueStrategy
data AssemblySet m =
AssemblySet { AssemblySet m -> Int
assemblySetSequenceNo :: Int,
AssemblySet m -> Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact :: Ref m (Maybe (ProcessId m)),
AssemblySet m -> Ref m Int
assemblySetAssemblingCounter :: Ref m Int,
AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
assemblySetGatheringTransacts :: StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m),
AssemblySet m -> Ref m Int
assemblySetGatheringCounter :: Ref m Int
}
instance MonadDES m => Eq (AssemblySet m) where
{-# INLINABLE (==) #-}
AssemblySet m
x == :: AssemblySet m -> AssemblySet m -> Bool
== AssemblySet m
y = (AssemblySet m -> Ref m (Maybe (ProcessId m))
forall (m :: * -> *). AssemblySet m -> Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact AssemblySet m
x) Ref m (Maybe (ProcessId m)) -> Ref m (Maybe (ProcessId m)) -> Bool
forall a. Eq a => a -> a -> Bool
== (AssemblySet m -> Ref m (Maybe (ProcessId m))
forall (m :: * -> *). AssemblySet m -> Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact AssemblySet m
y)
instance Hashable (AssemblySet m) where
hashWithSalt :: Int -> AssemblySet m -> Int
hashWithSalt Int
salt AssemblySet m
x = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (AssemblySet m -> Int
forall (m :: * -> *). AssemblySet m -> Int
assemblySetSequenceNo AssemblySet m
x)
newAssemblySet :: MonadDES m => Simulation m (AssemblySet m)
{-# INLINABLE newAssemblySet #-}
newAssemblySet :: Simulation m (AssemblySet m)
newAssemblySet =
(Run m -> m (AssemblySet m)) -> Simulation m (AssemblySet m)
forall (m :: * -> *) a. (Run m -> m a) -> Simulation m a
Simulation ((Run m -> m (AssemblySet m)) -> Simulation m (AssemblySet m))
-> (Run m -> m (AssemblySet m)) -> Simulation m (AssemblySet m)
forall a b. (a -> b) -> a -> b
$ \Run m
r ->
do let g :: Generator m
g = Run m -> Generator m
forall (m :: * -> *). Run m -> Generator m
runGenerator Run m
r
Int
sequenceNo <- Generator m -> m Int
forall (m :: * -> *). MonadGenerator m => Generator m -> m Int
generateSequenceNo Generator m
g
Ref m (Maybe (ProcessId m))
assemblingTransact <- Run m
-> Simulation m (Ref m (Maybe (ProcessId m)))
-> m (Ref m (Maybe (ProcessId m)))
forall (m :: * -> *) a. Run m -> Simulation m a -> m a
invokeSimulation Run m
r (Simulation m (Ref m (Maybe (ProcessId m)))
-> m (Ref m (Maybe (ProcessId m))))
-> Simulation m (Ref m (Maybe (ProcessId m)))
-> m (Ref m (Maybe (ProcessId m)))
forall a b. (a -> b) -> a -> b
$ Maybe (ProcessId m) -> Simulation m (Ref m (Maybe (ProcessId m)))
forall (m :: * -> *) a. MonadDES m => a -> Simulation m (Ref m a)
newRef Maybe (ProcessId m)
forall a. Maybe a
Nothing
Ref m Int
assemblingCounter <- Run m -> Simulation m (Ref m Int) -> m (Ref m Int)
forall (m :: * -> *) a. Run m -> Simulation m a -> m a
invokeSimulation Run m
r (Simulation m (Ref m Int) -> m (Ref m Int))
-> Simulation m (Ref m Int) -> m (Ref m Int)
forall a b. (a -> b) -> a -> b
$ Int -> Simulation m (Ref m Int)
forall (m :: * -> *) a. MonadDES m => a -> Simulation m (Ref m a)
newRef Int
0
StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
gatheringTransacts <- Run m
-> Simulation
m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m))
-> m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m))
forall (m :: * -> *) a. Run m -> Simulation m a -> m a
invokeSimulation Run m
r (Simulation
m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m))
-> m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)))
-> Simulation
m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m))
-> m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m))
forall a b. (a -> b) -> a -> b
$ TransactQueueStrategy FCFS
-> Simulation
m (StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m))
forall (m :: * -> *) s a.
QueueStrategy m s =>
s -> Simulation m (StrategyQueue m s a)
newStrategyQueue (FCFS -> TransactQueueStrategy FCFS
forall s. s -> TransactQueueStrategy s
TransactQueueStrategy FCFS
FCFS)
Ref m Int
gatheringCounter <- Run m -> Simulation m (Ref m Int) -> m (Ref m Int)
forall (m :: * -> *) a. Run m -> Simulation m a -> m a
invokeSimulation Run m
r (Simulation m (Ref m Int) -> m (Ref m Int))
-> Simulation m (Ref m Int) -> m (Ref m Int)
forall a b. (a -> b) -> a -> b
$ Int -> Simulation m (Ref m Int)
forall (m :: * -> *) a. MonadDES m => a -> Simulation m (Ref m a)
newRef Int
0
AssemblySet m -> m (AssemblySet m)
forall (m :: * -> *) a. Monad m => a -> m a
return AssemblySet :: forall (m :: * -> *).
Int
-> Ref m (Maybe (ProcessId m))
-> Ref m Int
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
-> Ref m Int
-> AssemblySet m
AssemblySet { assemblySetSequenceNo :: Int
assemblySetSequenceNo = Int
sequenceNo,
assemblySetAssemblingTransact :: Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact = Ref m (Maybe (ProcessId m))
assemblingTransact,
assemblySetAssemblingCounter :: Ref m Int
assemblySetAssemblingCounter = Ref m Int
assemblingCounter,
assemblySetGatheringTransacts :: StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
assemblySetGatheringTransacts = StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
gatheringTransacts,
assemblySetGatheringCounter :: Ref m Int
assemblySetGatheringCounter = Ref m Int
gatheringCounter
}
assembleTransact :: MonadDES m => Transact m a -> Int -> Process m ()
{-# INLINABLE assembleTransact #-}
assembleTransact :: Transact m a -> Int -> Process m ()
assembleTransact Transact m a
t Int
n =
do (AssemblySet m
s, Int
a) <-
Event m (AssemblySet m, Int) -> Process m (AssemblySet m, Int)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m (AssemblySet m, Int) -> Process m (AssemblySet m, Int))
-> Event m (AssemblySet m, Int) -> Process m (AssemblySet m, Int)
forall a b. (a -> b) -> a -> b
$
do AssemblySet m
s <- Transact m a -> Event m (AssemblySet m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (AssemblySet m)
transactAssemblySet Transact m a
t
Int
a <- Ref m Int -> Event m Int
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetAssemblingCounter AssemblySet m
s)
(AssemblySet m, Int) -> Event m (AssemblySet m, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (AssemblySet m
s, Int
a)
if Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do let n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
Bool -> Process m () -> Process m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
n' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Process m () -> Process m ()) -> Process m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
SimulationRetry -> Process m ()
forall (m :: * -> *) e a.
(MonadDES m, Exception e) =>
e -> Process m a
throwProcess (SimulationRetry -> Process m ())
-> SimulationRetry -> Process m ()
forall a b. (a -> b) -> a -> b
$
String -> SimulationRetry
SimulationRetry
String
"The number of transacts must be positive: assembleTransact"
if Int
n' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then () -> Process m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do Event m () -> Process m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m () -> Process m ()) -> Event m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
do ProcessId m
pid <- Transact m a -> Event m (ProcessId m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (ProcessId m)
requireTransactProcessId Transact m a
t
Ref m (Maybe (ProcessId m)) -> Maybe (ProcessId m) -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m (Maybe (ProcessId m))
forall (m :: * -> *). AssemblySet m -> Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact AssemblySet m
s) (ProcessId m -> Maybe (ProcessId m)
forall a. a -> Maybe a
Just ProcessId m
pid)
Ref m Int -> Int -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetAssemblingCounter AssemblySet m
s) (Int -> Event m ()) -> Int -> Event m ()
forall a b. (a -> b) -> a -> b
$! Int
n'
Process m ()
forall (m :: * -> *). MonadDES m => Process m ()
passivateProcess
else do let a' :: Int
a' = Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
if Int
a' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do Event m () -> Process m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m () -> Process m ()) -> Event m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
do Just ProcessId m
pid <- Ref m (Maybe (ProcessId m)) -> Event m (Maybe (ProcessId m))
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef (AssemblySet m -> Ref m (Maybe (ProcessId m))
forall (m :: * -> *). AssemblySet m -> Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact AssemblySet m
s)
Ref m (Maybe (ProcessId m)) -> Maybe (ProcessId m) -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m (Maybe (ProcessId m))
forall (m :: * -> *). AssemblySet m -> Ref m (Maybe (ProcessId m))
assemblySetAssemblingTransact AssemblySet m
s) Maybe (ProcessId m)
forall a. Maybe a
Nothing
Ref m Int -> Int -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetAssemblingCounter AssemblySet m
s) (Int -> Event m ()) -> Int -> Event m ()
forall a b. (a -> b) -> a -> b
$! Int
a'
ProcessId m -> Event m ()
forall (m :: * -> *). MonadDES m => ProcessId m -> Event m ()
reactivateProcessImmediately ProcessId m
pid
Process m ()
forall (m :: * -> *) a. MonadDES m => Process m a
cancelProcess
else do Event m () -> Process m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m () -> Process m ()) -> Event m () -> Process m ()
forall a b. (a -> b) -> a -> b
$ Ref m Int -> Int -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetAssemblingCounter AssemblySet m
s) (Int -> Event m ()) -> Int -> Event m ()
forall a b. (a -> b) -> a -> b
$! Int
a'
Process m ()
forall (m :: * -> *) a. MonadDES m => Process m a
cancelProcess
gatherTransacts :: MonadDES m => Transact m a -> Int -> Process m ()
{-# INLINABLE gatherTransacts #-}
gatherTransacts :: Transact m a -> Int -> Process m ()
gatherTransacts Transact m a
t Int
n =
do (AssemblySet m
s, Int
a) <-
Event m (AssemblySet m, Int) -> Process m (AssemblySet m, Int)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m (AssemblySet m, Int) -> Process m (AssemblySet m, Int))
-> Event m (AssemblySet m, Int) -> Process m (AssemblySet m, Int)
forall a b. (a -> b) -> a -> b
$
do AssemblySet m
s <- Transact m a -> Event m (AssemblySet m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (AssemblySet m)
transactAssemblySet Transact m a
t
Int
a <- Ref m Int -> Event m Int
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetGatheringCounter AssemblySet m
s)
(AssemblySet m, Int) -> Event m (AssemblySet m, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (AssemblySet m
s, Int
a)
if Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do let n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
Bool -> Process m () -> Process m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
n' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Process m () -> Process m ()) -> Process m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
SimulationRetry -> Process m ()
forall (m :: * -> *) e a.
(MonadDES m, Exception e) =>
e -> Process m a
throwProcess (SimulationRetry -> Process m ())
-> SimulationRetry -> Process m ()
forall a b. (a -> b) -> a -> b
$
String -> SimulationRetry
SimulationRetry
String
"The number of transacts must be positive: gatherTransacts"
if Int
n' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then () -> Process m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do Event m () -> Process m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m () -> Process m ()) -> Event m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
do ProcessId m
pid <- Transact m a -> Event m (ProcessId m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (ProcessId m)
requireTransactProcessId Transact m a
t
StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
-> Int -> ProcessId m -> Event m ()
forall (m :: * -> *) s p a.
PriorityQueueStrategy m s p =>
StrategyQueue m s a -> p -> a -> Event m ()
strategyEnqueueWithPriority
(AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
forall (m :: * -> *).
AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
assemblySetGatheringTransacts AssemblySet m
s)
(Transact m a -> Int
forall (m :: * -> *) a. Transact m a -> Int
transactPriority Transact m a
t)
ProcessId m
pid
Ref m Int -> Int -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetGatheringCounter AssemblySet m
s) (Int -> Event m ()) -> Int -> Event m ()
forall a b. (a -> b) -> a -> b
$! Int
n'
Process m ()
forall (m :: * -> *). MonadDES m => Process m ()
passivateProcess
else do let a' :: Int
a' = Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
Event m () -> Process m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m () -> Process m ()) -> Event m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
do ProcessId m
pid <- Transact m a -> Event m (ProcessId m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (ProcessId m)
requireTransactProcessId Transact m a
t
StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
-> Int -> ProcessId m -> Event m ()
forall (m :: * -> *) s p a.
PriorityQueueStrategy m s p =>
StrategyQueue m s a -> p -> a -> Event m ()
strategyEnqueueWithPriority
(AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
forall (m :: * -> *).
AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
assemblySetGatheringTransacts AssemblySet m
s)
(Transact m a -> Int
forall (m :: * -> *) a. Transact m a -> Int
transactPriority Transact m a
t)
ProcessId m
pid
Ref m Int -> Int -> Event m ()
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetGatheringCounter AssemblySet m
s) (Int -> Event m ()) -> Int -> Event m ()
forall a b. (a -> b) -> a -> b
$! Int
a'
if Int
a' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then Event m () -> Process m ()
forall (m :: * -> *). MonadDES m => Event m () -> Process m ()
passivateProcessBefore (Event m () -> Process m ()) -> Event m () -> Process m ()
forall a b. (a -> b) -> a -> b
$
Event m () -> Event m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
EventLift t m =>
Event m a -> t m a
liftEvent (Event m () -> Event m ()) -> Event m () -> Event m ()
forall a b. (a -> b) -> a -> b
$
do let loop :: [ProcessId m] -> Event m [ProcessId m]
loop [ProcessId m]
acc =
do Bool
f <- StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
-> Event m Bool
forall (m :: * -> *) s a.
QueueStrategy m s =>
StrategyQueue m s a -> Event m Bool
strategyQueueNull (AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
forall (m :: * -> *).
AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
assemblySetGatheringTransacts AssemblySet m
s)
if Bool
f
then [ProcessId m] -> Event m [ProcessId m]
forall (m :: * -> *) a. Monad m => a -> m a
return ([ProcessId m] -> [ProcessId m]
forall a. [a] -> [a]
reverse [ProcessId m]
acc)
else do ProcessId m
x <- StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
-> Event m (ProcessId m)
forall (m :: * -> *) s a.
DequeueStrategy m s =>
StrategyQueue m s a -> Event m a
strategyDequeue (AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
forall (m :: * -> *).
AssemblySet m
-> StrategyQueue m (TransactQueueStrategy FCFS) (ProcessId m)
assemblySetGatheringTransacts AssemblySet m
s)
[ProcessId m] -> Event m [ProcessId m]
loop (ProcessId m
xProcessId m -> [ProcessId m] -> [ProcessId m]
forall a. a -> [a] -> [a]
: [ProcessId m]
acc)
act :: [ProcessId m] -> Event m ()
act [] = () -> Event m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
act (ProcessId m
pid: [ProcessId m]
pids') =
do ProcessId m -> Event m ()
forall (m :: * -> *). MonadDES m => ProcessId m -> Event m ()
reactivateProcessImmediately ProcessId m
pid
Event m () -> Event m ()
forall (m :: * -> *). MonadDES m => Event m () -> Event m ()
yieldEvent (Event m () -> Event m ()) -> Event m () -> Event m ()
forall a b. (a -> b) -> a -> b
$ [ProcessId m] -> Event m ()
act [ProcessId m]
pids'
[ProcessId m]
pids <- [ProcessId m] -> Event m [ProcessId m]
loop []
[ProcessId m] -> Event m ()
forall (m :: * -> *). MonadDES m => [ProcessId m] -> Event m ()
act [ProcessId m]
pids
else Process m ()
forall (m :: * -> *). MonadDES m => Process m ()
passivateProcess
transactAssembling :: MonadDES m => Transact m a -> Event m Bool
{-# INLINABLE transactAssembling #-}
transactAssembling :: Transact m a -> Event m Bool
transactAssembling Transact m a
t =
do AssemblySet m
s <- Transact m a -> Event m (AssemblySet m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (AssemblySet m)
transactAssemblySet Transact m a
t
Int
a <- Ref m Int -> Event m Int
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetAssemblingCounter AssemblySet m
s)
Bool -> Event m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0)
transactGathering :: MonadDES m => Transact m a -> Event m Bool
{-# INLINABLE transactGathering #-}
transactGathering :: Transact m a -> Event m Bool
transactGathering Transact m a
t =
do AssemblySet m
s <- Transact m a -> Event m (AssemblySet m)
forall (m :: * -> *) a.
MonadDES m =>
Transact m a -> Event m (AssemblySet m)
transactAssemblySet Transact m a
t
Int
a <- Ref m Int -> Event m Int
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef (AssemblySet m -> Ref m Int
forall (m :: * -> *). AssemblySet m -> Ref m Int
assemblySetGatheringCounter AssemblySet m
s)
Bool -> Event m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0)