module Data.HashMap.Strict
(
HashMap
, empty
, singleton
, null
, size
, lookup
, lookupDefault
, insert
, delete
, insertWith
, adjust
, union
, unionWith
, map
, traverseWithKey
, difference
, intersection
, foldl'
, foldlWithKey'
, foldr
, foldrWithKey
, filter
, filterWithKey
, elems
, keys
, toList
, fromList
, fromListWith
) where
import Data.Hashable (Hashable(hash))
import Prelude hiding (filter, foldr, lookup, map, null)
import qualified Data.FullList.Strict as FL
import Data.HashMap.Common
import Data.HashMap.Lazy hiding (fromList, fromListWith, insert, insertWith,
adjust, map, singleton, unionWith)
import qualified Data.HashMap.Lazy as L
import qualified Data.List as List
singleton :: Hashable k => k -> v -> HashMap k v
singleton k !v = L.singleton k v
insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v
insert k0 !v0 t0 = go h0 k0 v0 t0
where
h0 = hash k0
go !h !k v t@(Bin sm l r)
| nomatch h sm = join h (Tip h $ FL.singleton k v) sm t
| zero h sm = Bin sm (go h k v l) r
| otherwise = Bin sm l (go h k v r)
go h k v t@(Tip h' l)
| h == h' = Tip h $ FL.insert k v l
| otherwise = join h (Tip h $ FL.singleton k v) h' t
go h k v Nil = Tip h $ FL.singleton k v
#if __GLASGOW_HASKELL__ >= 700
#endif
insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v
-> HashMap k v
insertWith f k0 !v0 t0 = go h0 k0 v0 t0
where
h0 = hash k0
go !h !k v t@(Bin sm l r)
| nomatch h sm = join h (Tip h $ FL.singleton k v) sm t
| zero h sm = Bin sm (go h k v l) r
| otherwise = Bin sm l (go h k v r)
go h k v t@(Tip h' l)
| h == h' = Tip h $ FL.insertWith f k v l
| otherwise = join h (Tip h $ FL.singleton k v) h' t
go h k v Nil = Tip h $ FL.singleton k v
#if __GLASGOW_HASKELL__ >= 700
#endif
adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v
adjust f k0 t0 = go h0 k0 t0
where
h0 = hash k0
go !h !k t@(Bin sm l r)
| nomatch h sm = t
| zero h sm = Bin sm (go h k l) r
| otherwise = Bin sm l (go h k r)
go h k t@(Tip h' l)
| h == h' = Tip h $ FL.adjust f k l
| otherwise = t
go _ _ Nil = Nil
#if __GLASGOW_HASKELL__ >= 700
#endif
map :: (v1 -> v2) -> HashMap k v1 -> HashMap k v2
map f = go
where
go (Bin sm l r) = Bin sm (go l) (go r)
go (Tip h l) = Tip h (FL.map f' l)
go Nil = Nil
f' k v = (k, f v)
unionWith :: Eq k => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
unionWith f t1@(Bin sm1 l1 r1) t2@(Bin sm2 l2 r2)
| sm1 == sm2 = Bin sm1 (unionWith f l1 l2) (unionWith f r1 r2)
| shorter sm1 sm2 = union1
| shorter sm2 sm1 = union2
| otherwise = join sm1 t1 sm2 t2
where
union1 | nomatch sm2 sm1 = join sm1 t1 sm2 t2
| zero sm2 sm1 = Bin sm1 (unionWith f l1 t2) r1
| otherwise = Bin sm1 l1 (unionWith f r1 t2)
union2 | nomatch sm1 sm2 = join sm1 t1 sm2 t2
| zero sm1 sm2 = Bin sm2 (unionWith f t1 l2) r2
| otherwise = Bin sm2 l2 (unionWith f t1 r2)
unionWith f (Tip h l) t = insertCollidingWith (FL.unionWith f) h l t
unionWith f t (Tip h l) = insertCollidingWith (flip (FL.unionWith f)) h l t
unionWith _ Nil t = t
unionWith _ t Nil = t
#if __GLASGOW_HASKELL__ >= 700
#endif
fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v
fromList = List.foldl' (\ m (k, v) -> insert k v m) empty
fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v
fromListWith f = List.foldl' (\ m (k, v) -> insertWith f k v m) empty