{- - Copyright (c) 2008, Jochem Berndsen - All rights reserved. - - Redistribution and use in source and binary forms, with or without - modification, are permitted provided that the following conditions - are met: - - 1. Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - 2. Redistributions in binary form must reproduce the above copyright - notice, this list of conditions and the following disclaimer in the - documentation and/or other materials provided with the distribution. - 3. Neither the name of the author nor the names of its contributors - may be used to endorse or promote products derived from this software - without specific prior written permission. - - THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDER AND CONTRIBUTORS - ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED - TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR - PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS - BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR - CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF - SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS - INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN - CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) - ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE - POSSIBILITY OF SUCH DAMAGE. -} -- | -- Module : Control.Hasim.WatchMap -- Copyright : (c) Jochem Berndsen 2008 -- License : BSD3 -- -- Maintainer : jochem@functor.nl -- Stability : experimental -- Portability : unportable -- -- This module defines a 'WatchMap', a data structure that keeps track -- of which processes watch which other processes. module Control.Hasim.WatchMap ( -- * Abstract data type WatchMap, -- * Creation and inspection emptyWM, watchers, -- * Modification register, unregister ) where import Control.Hasim.Process (Process) import Data.Set (Set) import qualified Data.Set as S -- | A watch map. This data structure represents a relation on -- processes. newtype WatchMap = WM { unWM :: Set (Process, Process) } -- | Add the tuple @(p1, p2)@ to the relation. register :: Process -- ^ @p1@ -> Process -- ^ @p2@ -> WatchMap -- ^ old 'WatchMap' -> WatchMap -- ^ new 'WatchMap' register p1 p2 = WM . S.union (S.singleton (p1, p2)) . unWM -- | Remove the tuple @(p1, p2)@ from the relation, if it existed. unregister :: Process -- ^ @p1@ -> Process -- ^ @p2@ -> WatchMap -- ^ old 'WatchMap' -> WatchMap -- ^ new 'WatchMap' unregister p1 p2 = WM . flip S.difference (S.singleton (p1, p2)) . unWM -- | Find all @p1@ such that @(p1, p2)@ is in the relation. watchers :: WatchMap -- ^ The 'WatchMap' to be queried -> Process -- ^ @p2@ -> [Process] -- ^ The list of @p1@'s watchers = flip f where f :: Process -> WatchMap -> [Process] f p = map fst . S.toList . S.filter ((== p) . snd) . unWM -- | An empty 'WatchMap'. emptyWM :: WatchMap emptyWM = WM S.empty