module STMContainers.Bimap
(
Bimap,
Association,
Key,
new,
newIO,
insert1,
insert2,
delete1,
delete2,
deleteAll,
lookup1,
lookup2,
focus1,
focus2,
null,
size,
stream,
)
where
import STMContainers.Prelude hiding (insert, delete, lookup, alter, foldM, toList, empty, null)
import qualified Focus
import qualified STMContainers.Map as Map
data Bimap a b =
Bimap {m1 :: !(Map.Map a b), m2 :: !(Map.Map b a)}
deriving (Typeable)
type Association a b = (Key a, Key b)
type Key k = Map.Key k
new :: STM (Bimap a b)
new = Bimap <$> Map.new <*> Map.new
newIO :: IO (Bimap a b)
newIO = Bimap <$> Map.newIO <*> Map.newIO
null :: Bimap a b -> STM Bool
null = Map.null . m1
size :: Bimap a b -> STM Int
size = Map.size . m1
lookup1 :: (Association a b) => a -> Bimap a b -> STM (Maybe b)
lookup1 k = Map.lookup k . m1
lookup2 :: (Association a b) => b -> Bimap a b -> STM (Maybe a)
lookup2 k = Map.lookup k . m2
insert1 :: (Association a b) => b -> a -> Bimap a b -> STM ()
insert1 b a (Bimap m1 m2) =
do
Map.insert b a m1
Map.insert a b m2
insert2 :: (Association a b) => a -> b -> Bimap a b -> STM ()
insert2 b a (Bimap m1 m2) = (inline insert1) b a (Bimap m2 m1)
delete1 :: (Association a b) => a -> Bimap a b -> STM ()
delete1 k (Bimap m1 m2) =
Map.focus lookupAndDeleteStrategy k m1 >>=
mapM_ (\k' -> Map.delete k' m2)
where
lookupAndDeleteStrategy r =
return (r, Focus.Remove)
delete2 :: (Association a b) => b -> Bimap a b -> STM ()
delete2 k (Bimap m1 m2) = (inline delete1) k (Bimap m2 m1)
deleteAll :: Bimap a b -> STM ()
deleteAll (Bimap m1 m2) =
do
Map.deleteAll m1
Map.deleteAll m2
focus1 :: (Association a b) => Focus.StrategyM STM b r -> a -> Bimap a b -> STM r
focus1 s a (Bimap m1 m2) =
do
(r, d, mb) <- Map.focus s' a m1
case d of
Focus.Keep ->
return ()
Focus.Remove ->
forM_ mb $ \b -> Map.delete b m2
Focus.Replace b' ->
do
forM_ mb $ \b -> Map.delete b m2
Map.insert a b' m2
return r
where
s' = \k -> s k >>= \(r, d) -> return ((r, d, k), d)
focus2 :: (Association a b) => Focus.StrategyM STM a r -> b -> Bimap a b -> STM r
focus2 s b (Bimap m1 m2) = (inline focus1) s b (Bimap m2 m1)
stream :: Bimap a b -> ListT STM (a, b)
stream = Map.stream . m1