Copyright | (c) klapaucius swamp_agr 2016-2021 |
---|---|
License | BSD3 |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newtype Dictionary s ks k vs v = DRef {
- getDRef :: MutVar s (Dictionary_ s ks k vs v)
- data FrozenDictionary ks k vs v = FrozenDictionary {}
- findElem :: (Vector ks k, Vector vs v, Hashable k, Eq k) => FrozenDictionary ks k vs v -> k -> Int
- data Dictionary_ s ks k vs v = Dictionary {}
- findEntry :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m Int
- initialize :: (MVector ks k, MVector vs v, PrimMonad m) => Int -> m (Dictionary (PrimState m) ks k vs v)
- clone :: (MVector ks k, MVector vs v, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v)
- null :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Bool
- size :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Int
- keys :: (Vector ks k, PrimMonad m) => Dictionary (PrimState m) (Mutable ks) k vs v -> m (ks k)
- values :: (Vector vs v, PrimMonad m) => Dictionary (PrimState m) ks k (Mutable vs) v -> m (vs v)
- lookup :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m (Maybe v)
- lookup' :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m v
- insert :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> v -> m ()
- delete :: (Eq k, MVector ks k, MVector vs v, Hashable k, PrimMonad m, DeleteEntry ks, DeleteEntry vs) => Dictionary (PrimState m) ks k vs v -> k -> m ()
- alterM :: (MVector ks k, MVector vs v, DeleteEntry ks, DeleteEntry vs, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> (Maybe v -> m (Maybe v)) -> k -> m ()
- union :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v)
- unionWith :: (MVector ks k, MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => (v -> v -> v) -> Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v)
- unionWithKey :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => (k -> v -> v -> v) -> Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v)
- difference :: (MVector ks k, MVector vs v, MVector vs w, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs w -> m (Dictionary (PrimState m) ks k vs v)
- differenceWith :: (MVector ks k, MVector vs v, MVector vs w, PrimMonad m, Hashable k, Eq k) => (v -> w -> Maybe v) -> Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs w -> m (Dictionary (PrimState m) ks k vs v)
- intersection :: (MVector ks k, MVector vs v, MVector vs w, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs w -> m (Dictionary (PrimState m) ks k vs v)
- intersectionWith :: (MVector ks k, MVector vs v1, MVector vs v2, MVector vs v3, PrimMonad m, Hashable k, Eq k) => (v1 -> v2 -> v3) -> Dictionary (PrimState m) ks k vs v1 -> Dictionary (PrimState m) ks k vs v2 -> m (Dictionary (PrimState m) ks k vs v3)
- intersectionWithKey :: (MVector ks k, MVector vs v1, MVector vs v2, MVector vs v3, PrimMonad m, Hashable k, Eq k) => (k -> v1 -> v2 -> v3) -> Dictionary (PrimState m) ks k vs v1 -> Dictionary (PrimState m) ks k vs v2 -> m (Dictionary (PrimState m) ks k vs v3)
- unsafeFreeze :: (Vector ks k, Vector vs v, PrimMonad m) => Dictionary (PrimState m) (Mutable ks) k (Mutable vs) v -> m (FrozenDictionary ks k vs v)
- unsafeThaw :: (Vector ks k, Vector vs v, PrimMonad m) => FrozenDictionary ks k vs v -> m (Dictionary (PrimState m) (Mutable ks) k (Mutable vs) v)
- fromList :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => [(k, v)] -> m (Dictionary (PrimState m) ks k vs v)
- toList :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> m [(k, v)]
- module Control.Monad.Primitive
Documentation
- This package provides hashtable implementation similar to .NET Generic Dictionary implementation (at the time of 2015) https://github.com/dotnet/coreclr/blob/3a0d638843472056c0cbb723beaed0b1152ca36d/src/mscorlib/src/System/Collections/Generic/Dictionary.cs.
- It was originated as response to https://comp.lang.functional.narkive.com/uYVjkKfl/f-vs-ocaml-vs-python-vs-haskell-hash-table-performance#post5.
- For more hashtables implementations see https://rcoh.me/posts/hash-map-analysis/.
Usage
>>>
import qualified Data.Vector.Storable.Mutable as VM
>>>
import qualified Data.Vector.Unboxed.Mutable as UM
>>>
import Data.Vector.Hashtables
>>>
type HashTable k v = Dictionary (PrimState IO) VM.MVector k UM.MVector v
>>>
ht <- initialize 0 :: IO (HashTable Int Int)
>>>
insert ht 0 1
Types
newtype Dictionary s ks k vs v Source #
Single-element mutable array of Dictionary_
with primitive state token parameterized with state, keys and values types.
- Example*:
>>>
import qualified Data.Vector.Storable.Mutable as VM
>>>
import qualified Data.Vector.Unboxed.Mutable as UM
>>>
import Data.Vector.Hashtables
>>>
type HashTable k v = Dictionary (PrimState IO) VM.MVector k UM.MVector v
Different vectors could be used for keys and values:
- storable,
- mutable,
- unboxed.
In most cases unboxed vectors should be used. Nevertheless, it is up to you to decide about final form of hastable.
DRef | |
|
data FrozenDictionary ks k vs v Source #
Represents immutable dictionary as collection of immutable arrays and vectors.
See unsafeFreeze
and unsafeThaw
for conversions from/to mutable dictionary.
Instances
findElem :: (Vector ks k, Vector vs v, Hashable k, Eq k) => FrozenDictionary ks k vs v -> k -> Int Source #
O(1) in the best case, O(n) in the worst case.
Find dictionary entry by given key in immutable FrozenDictionary
.
If entry not found -1
returned.
data Dictionary_ s ks k vs v Source #
Represents collection of hashtable internal primitive arrays and vectors.
- hash codes,
- references to the next element,
- buckets,
- keys
- and values.
findEntry :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m Int Source #
O(1) in the best case, O(n) in the worst case.
Find dictionary entry by given key. If entry not found -1
returned.
Construction
initialize :: (MVector ks k, MVector vs v, PrimMonad m) => Int -> m (Dictionary (PrimState m) ks k vs v) Source #
O(1) Dictionary with given capacity.
clone :: (MVector ks k, MVector vs v, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v) Source #
Create a copy of mutable dictionary.
Basic interface
size :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Int Source #
O(1) Return the number of non-empty entries of dictionary. Synonym of length
.
keys :: (Vector ks k, PrimMonad m) => Dictionary (PrimState m) (Mutable ks) k vs v -> m (ks k) Source #
O(n) Retrieve list of keys from Dictionary
.
values :: (Vector vs v, PrimMonad m) => Dictionary (PrimState m) ks k (Mutable vs) v -> m (vs v) Source #
O(n) Retrieve list of values from Dictionary
.
lookup :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m (Maybe v) Source #
O(1) in the best case, O(n) in the worst case.
Find value by given key in Dictionary
. Like lookup'
but return Nothing
if value not found.
lookup' :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m v Source #
O(1) in the best case, O(n) in the worst case.
Find value by given key in Dictionary
. Throws an error if value not found.
insert :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> v -> m () Source #
O(1) in the best case, O(n) in the worst case. Insert key and value in dictionary by key's hash. If entry with given key found value will be replaced.
delete :: (Eq k, MVector ks k, MVector vs v, Hashable k, PrimMonad m, DeleteEntry ks, DeleteEntry vs) => Dictionary (PrimState m) ks k vs v -> k -> m () Source #
O(1) in the best case, O(n) in the worst case.
Delete entry from Dictionary
by given key.
alterM :: (MVector ks k, MVector vs v, DeleteEntry ks, DeleteEntry vs, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> (Maybe v -> m (Maybe v)) -> k -> m () Source #
O(1) in the best case, O(n) in the worst case.
The expression (
) alters the value alterM
ht f kx
at k
, or absence thereof.
alterM
can be used to insert, delete, or update a value in a Dictionary
in the same
.PrimMonad
m
Combine
Union
union :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v) Source #
O(min n m) in the best case, O(min n m * max n m) in the worst case. The union of two maps. If a key occurs in both maps, the mapping from the first will be the mapping in the result.
unionWith :: (MVector ks k, MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => (v -> v -> v) -> Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v) Source #
O(min n m) in the best case, O(min n m * max n m) in the worst case. The union of two maps. The provided function (first argument) will be used to compute the result.
unionWithKey :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => (k -> v -> v -> v) -> Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs v -> m (Dictionary (PrimState m) ks k vs v) Source #
O(min n m) in the best case, O(min n m * max n m) in the worst case. The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.
Difference
difference :: (MVector ks k, MVector vs v, MVector vs w, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs w -> m (Dictionary (PrimState m) ks k vs v) Source #
O(n) in the best case, O(n * m) in the worst case. Difference of two tables. Return elements of the first table not existing in the second.
differenceWith :: (MVector ks k, MVector vs v, MVector vs w, PrimMonad m, Hashable k, Eq k) => (v -> w -> Maybe v) -> Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs w -> m (Dictionary (PrimState m) ks k vs v) Source #
O(n) in the best case, O(n * m) in the worst case.
Difference with a combining function. When two equal keys are
encountered, the combining function is applied to the values of these keys.
If it returns Nothing
, the element is discarded (proper set difference). If
it returns (
), the element is updated with a new value Just
yy
.
Intersection
intersection :: (MVector ks k, MVector vs v, MVector vs w, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> Dictionary (PrimState m) ks k vs w -> m (Dictionary (PrimState m) ks k vs v) Source #
O(n) in the best case, O(n * m) in the worst case. Intersection of two maps. Return elements of the first map for keys existing in the second.
intersectionWith :: (MVector ks k, MVector vs v1, MVector vs v2, MVector vs v3, PrimMonad m, Hashable k, Eq k) => (v1 -> v2 -> v3) -> Dictionary (PrimState m) ks k vs v1 -> Dictionary (PrimState m) ks k vs v2 -> m (Dictionary (PrimState m) ks k vs v3) Source #
Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.
intersectionWithKey :: (MVector ks k, MVector vs v1, MVector vs v2, MVector vs v3, PrimMonad m, Hashable k, Eq k) => (k -> v1 -> v2 -> v3) -> Dictionary (PrimState m) ks k vs v1 -> Dictionary (PrimState m) ks k vs v2 -> m (Dictionary (PrimState m) ks k vs v3) Source #
Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.
Conversions
Mutable
unsafeFreeze :: (Vector ks k, Vector vs v, PrimMonad m) => Dictionary (PrimState m) (Mutable ks) k (Mutable vs) v -> m (FrozenDictionary ks k vs v) Source #
O(1) Unsafe convert a mutable dictionary to an immutable one without copying. The mutable dictionary may not be used after this operation.
unsafeThaw :: (Vector ks k, Vector vs v, PrimMonad m) => FrozenDictionary ks k vs v -> m (Dictionary (PrimState m) (Mutable ks) k (Mutable vs) v) Source #
O(1) Unsafely convert immutable FrozenDictionary
to a mutable Dictionary
without copying.
The immutable dictionary may not be used after this operation.
List
fromList :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => [(k, v)] -> m (Dictionary (PrimState m) ks k vs v) Source #
O(n) Convert list to a Dictionary
.
toList :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> m [(k, v)] Source #
O(n) Convert Dictionary
to a list.
module Control.Monad.Primitive