{-# LANGUAGE CPP, BangPatterns #-}
module Network.Wai.Handler.Warp.MultiMap (
MMap
, isEmpty
, empty
, singleton
, insert
, search
, searchWith
, pruneWith
, toList
, merge
) where
#if __GLASGOW_HASKELL__ < 709
import Control.Applicative ((<$>))
#endif
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as I
import qualified Network.Wai.Handler.Warp.Some as S
type MMap v = IntMap (S.Some v)
isEmpty :: MMap v -> Bool
isEmpty = I.null
empty :: MMap v
empty = I.empty
singleton :: Int -> v -> MMap v
singleton k v = I.singleton k (S.singleton v)
search :: Int -> MMap v -> Maybe v
search k m = case I.lookup k m of
Nothing -> Nothing
Just s -> Just $! S.top s
searchWith :: Int -> (v -> Bool) -> MMap v -> Maybe v
searchWith k f m = case I.lookup k m of
Nothing -> Nothing
Just s -> S.lookupWith f s
insert :: Int -> v -> MMap v -> MMap v
insert k v m = I.insertWith S.union k (S.singleton v) m
toList :: MMap v -> [v]
toList m = concatMap f $ I.toAscList m
where
f (_,s) = S.toList s
pruneWith :: MMap v
-> (v -> IO Bool)
-> IO (MMap v)
pruneWith m action = I.fromAscList <$> go (I.toDescList m) []
where
go [] acc = return acc
go ((k,s):kss) acc = do
mt <- S.prune action s
case mt of
Nothing -> go kss acc
Just t -> go kss ((k,t) : acc)
merge :: MMap v -> MMap v -> MMap v
merge m1 m2 = I.unionWith S.union m1 m2