module Simulation.Aivika.GPSS.MatchChain
(MatchChain,
newMatchChain,
matchTransact,
transactMatching,
transactMatchingChanged,
transactMatchingChangedByTransact_,
transactMatchingChangedByAssemblySet_) where
import Data.IORef
import Control.Monad
import Control.Monad.Trans
import qualified Data.HashMap.Lazy as HM
import Simulation.Aivika
import Simulation.Aivika.GPSS.Transact
import Simulation.Aivika.GPSS.AssemblySet
data MatchChain =
MatchChain { matchChainMap :: IORef (HM.HashMap AssemblySet ProcessId),
matchChainSource :: SignalSource AssemblySet
}
newMatchChain :: Simulation MatchChain
newMatchChain =
do map <- liftIO $ newIORef HM.empty
src <- newSignalSource
return MatchChain { matchChainMap = map,
matchChainSource = src
}
matchTransact :: MatchChain -> Transact a -> Process ()
matchTransact chain t =
do (map, set) <-
liftEvent $
do map <- liftIO $ readIORef (matchChainMap chain)
set <- transactAssemblySet t
return (map, set)
case HM.lookup set map of
Just pid ->
liftEvent $
do liftIO $ modifyIORef (matchChainMap chain) $
HM.delete set
yieldEvent $
triggerSignal (matchChainSource chain) set
reactivateProcess pid
Nothing ->
do liftEvent $
do pid <- requireTransactProcessId t
liftIO $ modifyIORef (matchChainMap chain) $
HM.insert set pid
yieldEvent $
triggerSignal (matchChainSource chain) set
passivateProcess
transactMatching :: MatchChain -> AssemblySet -> Event Bool
transactMatching chain set =
do map <- liftIO $ readIORef (matchChainMap chain)
return (HM.member set map)
transactMatchingChangedByAssemblySet_ :: MatchChain -> AssemblySet -> Signal ()
transactMatchingChangedByAssemblySet_ chain set =
mapSignal (const ()) $
filterSignal (== set) $
transactMatchingChanged chain
transactMatchingChangedByTransact_ :: MatchChain -> Transact a -> Signal ()
transactMatchingChangedByTransact_ chain t =
mapSignal (const ()) $
filterSignalM pred $
transactMatchingChanged chain
where pred set =
do set' <- transactAssemblySet t
return (set == set')
transactMatchingChanged :: MatchChain -> Signal AssemblySet
transactMatchingChanged chain =
publishSignal (matchChainSource chain)