module Simulation.Aivika.Trans.GPSS.Block.Terminate
(terminateBlock,
terminateBlockByCount,
terminateBlockByCountM) where
import Control.Monad
import Control.Monad.Trans
import Simulation.Aivika.Trans
import Simulation.Aivika.Trans.GPSS.Block
terminateBlock :: MonadDES m => Block m a ()
terminateBlock =
Block { blockProcess = \a -> return () }
terminateBlockByCountM :: MonadDES m
=> Ref m Int
-> Event m Int
-> Block m a ()
terminateBlockByCountM counter decrement =
Block { blockProcess = \a -> action }
where
action =
liftEvent $
do i <- decrement
n <- readRef counter
let n' = n i
n' `seq` writeRef counter n'
when (n' <= 0) $
throwEvent $
SimulationAbort "Terminated by exceeding the counter"
terminateBlockByCount :: MonadDES m
=> Ref m Int
-> Int
-> Block m a ()
terminateBlockByCount counter i =
Block { blockProcess = \a -> action }
where
action =
liftEvent $
do n <- readRef counter
let n' = n i
n' `seq` writeRef counter n'
when (n' <= 0) $
throwEvent $
SimulationAbort "Terminated by exceeding the counter"