{-# LANGUAGE BangPatterns #-}
module Network.Wai.Handler.Warp.MultiMap (
MultiMap
, isEmpty
, empty
, singleton
, insert
, Network.Wai.Handler.Warp.MultiMap.lookup
, pruneWith
, toList
, merge
) where
import Data.Hashable (hash)
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as I
import Data.Semigroup
import Prelude
newtype MultiMap v = MultiMap (IntMap [(FilePath,v)])
empty :: MultiMap v
empty = MultiMap $ I.empty
isEmpty :: MultiMap v -> Bool
isEmpty (MultiMap mm) = I.null mm
singleton :: FilePath -> v -> MultiMap v
singleton path v = MultiMap mm
where
!h = hash path
!mm = I.singleton h [(path,v)]
lookup :: FilePath -> MultiMap v -> Maybe v
lookup path (MultiMap mm) = case I.lookup h mm of
Nothing -> Nothing
Just s -> Prelude.lookup path s
where
!h = hash path
insert :: FilePath -> v -> MultiMap v -> MultiMap v
insert path v (MultiMap mm) = MultiMap mm'
where
!h = hash path
!mm' = I.insertWith (<>) h [(path,v)] mm
toList :: MultiMap v -> [(FilePath,v)]
toList (MultiMap mm) = concatMap snd $ I.toAscList mm
pruneWith :: MultiMap v
-> ((FilePath,v) -> IO Bool)
-> IO (MultiMap v)
pruneWith (MultiMap mm) action = MultiMap <$> mm'
where
!mm' = I.fromAscList <$> go (I.toDescList mm) []
go [] !acc = return acc
go ((h,s):kss) !acc = do
rs <- prune action s
case rs of
[] -> go kss acc
_ -> go kss ((h,rs) : acc)
merge :: MultiMap v -> MultiMap v -> MultiMap v
merge (MultiMap m1) (MultiMap m2) = MultiMap mm
where
!mm = I.unionWith (<>) m1 m2
prune :: ((FilePath,v) -> IO Bool) -> [(FilePath,v)] -> IO [(FilePath,v)]
prune action xs0 = go xs0
where
go [] = return []
go (x:xs) = do
keep <- action x
rs <- go xs
return $ if keep then x:rs else rs