{-# LANGUAGE BangPatterns #-}
module Network.Wai.Handler.Warp.HashMap where
import Data.Hashable (hash)
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as I
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Prelude hiding (lookup)
newtype HashMap v = HashMap (IntMap (Map FilePath v))
empty :: HashMap v
empty = HashMap I.empty
isEmpty :: HashMap v -> Bool
isEmpty (HashMap hm) = I.null hm
insert :: FilePath -> v -> HashMap v -> HashMap v
insert path v (HashMap hm) = HashMap $ I.insertWith f h m hm
where
!h = hash path
!m = M.singleton path v
f = M.union
lookup :: FilePath -> HashMap v -> Maybe v
lookup path (HashMap hm) = I.lookup h hm >>= M.lookup path
where
!h = hash path