module Data.LinkedHashMap.IntMap
(
LinkedHashMap(..)
, empty
, singleton
, null
, size
, member
, lookup
, lookupDefault
, (!)
, insert
, delete
, map
, keys
, elems
, toList
, fromList
)
where
import Prelude hiding (null, lookup)
import Data.IORef
import System.IO.Unsafe
import Data.Hashable (Hashable)
import Control.DeepSeq (NFData(rnf))
import qualified Data.Foldable as F
import qualified Data.HashMap.Strict as M
import qualified Data.IntMap.Strict as IM
newtype Entry a = Entry { unEntry :: (Int, a) } deriving (Show)
instance Eq a => Eq (Entry a) where
(Entry (_, a)) == (Entry (_, b)) = a == b
data LinkedHashMap k v = LinkedHashMap (M.HashMap k (Entry v)) (IM.IntMap (k, v)) (IORef Int)
instance (Show k, Show v) => Show (LinkedHashMap k v) where
showsPrec d m@(LinkedHashMap _ _ _) = showParen (d > 10) $
showString "fromList " . shows (toList m)
newCounter :: Int -> IORef Int
newCounter n = unsafePerformIO (newIORef n)
getCounter :: IORef Int -> Int
getCounter rn = unsafePerformIO $ readIORef rn
incCounter :: IORef Int -> Int
incCounter rn = unsafePerformIO $ atomicModifyIORef rn $ \n -> (n + 1, n + 1)
lookup :: (Eq k, Hashable k) => k -> LinkedHashMap k v -> Maybe v
lookup k0 (LinkedHashMap m0 _ _) = case M.lookup k0 m0 of
Just (Entry (_, v)) -> Just v
Nothing -> Nothing
empty :: LinkedHashMap k v
empty = LinkedHashMap M.empty IM.empty (newCounter minBound)
singleton :: (Eq k, Hashable k) => k -> v -> LinkedHashMap k v
singleton k v = fromList [(k, v)]
keys :: (Eq k, Hashable k) => LinkedHashMap k v -> [k]
keys m = map (\(k, _) -> k) $ toList m
elems :: (Eq k, Hashable k) => LinkedHashMap k v -> [v]
elems m = map (\(_, v) -> v) $ toList m
fromList :: (Eq k, Hashable k) => [(k, v)] -> LinkedHashMap k v
fromList = F.foldl' (\m (k, v) -> insert k v m) empty
toList :: LinkedHashMap k v -> [(k, v)]
toList (LinkedHashMap _ s _) = IM.elems s
insert :: (Eq k, Hashable k) => k -> v -> LinkedHashMap k v -> LinkedHashMap k v
insert k v (LinkedHashMap m s rn) = s' `seq` LinkedHashMap m' s' rn
where
m' = M.insert k (Entry (n', v)) m
s' = IM.insert n' (k, v) s
n' = case M.lookup k m of
Just (Entry (n, _)) -> n
Nothing -> incCounter rn
delete :: (Eq k, Hashable k) => k -> LinkedHashMap k v -> LinkedHashMap k v
delete k0 (LinkedHashMap m s rn) = LinkedHashMap (M.delete k0 m) (case M.lookup k0 m of
Nothing -> s
Just (Entry (i, _)) -> IM.delete i s) rn
null :: LinkedHashMap k v -> Bool
null (LinkedHashMap m _ _) = M.null m
member :: (Eq k, Hashable k) => k -> LinkedHashMap k a -> Bool
member k m = case lookup k m of
Nothing -> False
Just _ -> True
size :: LinkedHashMap k v -> Int
size (LinkedHashMap _ s _) = IM.size s
lookupDefault :: (Eq k, Hashable k)
=> v
-> k -> LinkedHashMap k v -> v
lookupDefault def k t = case lookup k t of
Just v -> v
_ -> def
(!) :: (Eq k, Hashable k) => LinkedHashMap k v -> k -> v
(!) m k = case lookup k m of
Just v -> v
Nothing -> error "Data.LinkedHashMap.IntMap.(!): key not found"
instance (NFData a) => NFData (Entry a) where
rnf (Entry a) = rnf a
instance (NFData k, NFData v) => NFData (LinkedHashMap k v) where
rnf (LinkedHashMap m s _) = rnf m `seq` rnf s