Copyright | (c) klapaucius swamp_agr 2016-2021 |
---|---|
License | BSD3 |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type IntArray s = MutablePrimArray s Int
- newtype Dictionary s ks k vs v = DRef {
- getDRef :: MutVar s (Dictionary_ s ks k vs v)
- data Dictionary_ s ks k vs v = Dictionary {}
- getCount :: Int
- getFreeList :: Int
- getFreeCount :: Int
- 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
- (!~) :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> m a
- (!.~) :: Vector v a => v a -> Int -> a
- (<~~) :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> a -> m ()
- (!) :: PrimMonad m => MutablePrimArray (PrimState m) Int -> Int -> m Int
- (!.) :: PrimArray Int -> Int -> Int
- (<~) :: PrimMonad m => MutablePrimArray (PrimState m) Int -> Int -> Int -> m ()
- 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)
- 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)
- 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)
- at :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m v
- at' :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m (Maybe v)
- atWithOrElse :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> (Dictionary (PrimState m) ks k vs v -> Int -> m a) -> (Dictionary (PrimState m) ks k vs v -> m a) -> m a
- findEntry :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m Int
- findEntry_ :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary_ (PrimState m) ks k vs v -> k -> m Int
- insert :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> v -> m ()
- insertWithIndex :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Int -> Int -> k -> v -> MutVar (PrimState m) (Dictionary_ (PrimState m) ks k vs v) -> Dictionary_ (PrimState m) ks k vs v -> Int -> m ()
- addOrResize :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Int -> Int -> k -> v -> MutVar (PrimState m) (Dictionary_ (PrimState m) ks k vs v) -> Dictionary_ (PrimState m) ks k vs v -> m ()
- add :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Int -> Int -> Int -> k -> v -> Dictionary_ (PrimState m) ks k vs v -> m ()
- resize :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary_ (PrimState m) ks k vs v -> Int -> Int -> k -> v -> m (Dictionary_ (PrimState m) ks k vs v)
- class DeleteEntry xs where
- deleteEntry :: (MVector xs x, PrimMonad m) => xs (PrimState m) x -> Int -> 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 ()
- deleteWithIndex :: (Eq k, MVector ks k, MVector vs v, Hashable k, PrimMonad m, DeleteEntry ks, DeleteEntry vs) => Int -> Int -> Dictionary_ (PrimState m) ks k vs v -> k -> Int -> Int -> m ()
- 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
- lookupIndex :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m (Maybe Int)
- null :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Bool
- length :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Int
- size :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Int
- member :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m Bool
- findWithDefault :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> v -> k -> m v
- upsert :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> (Maybe v -> v) -> k -> m ()
- alter :: (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 -> Maybe 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)
- 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)]
- primesWithFastRem :: Vector (Int, Int, Int)
- getFastRem :: Int -> FastRem
- data FastRem = FastRem {}
- fastRem :: Int -> FastRem -> Int
Documentation
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.
Different flavors of MVector
could be used for keys and values.
It's preferable to use Data.Vector.Unboxed.Mutable
or Data.Vector.Storable.Mutable if possible. Otherwise,
if you must use boxed vectors, consider employing strict ones from
strict-containers
to eliminate potential accumulation of thunks.
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
DRef | |
|
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.
getFreeList :: Int Source #
getFreeCount :: Int Source #
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.
(!~) :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> m a Source #
Infix version of unsafeRead
.
(<~~) :: (MVector v a, PrimMonad m) => v (PrimState m) a -> Int -> a -> m () Source #
Infix version of unsafeWrite
.
(!) :: PrimMonad m => MutablePrimArray (PrimState m) Int -> Int -> m Int Source #
Infix version of readPrimArray
.
(<~) :: PrimMonad m => MutablePrimArray (PrimState m) Int -> Int -> Int -> m () Source #
Infix version of writePrimArray
.
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.
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.
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
.
at :: (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.
at' :: (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 at'
but return Nothing
if value not found.
atWithOrElse :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> (Dictionary (PrimState m) ks k vs v -> Int -> m a) -> (Dictionary (PrimState m) ks k vs v -> m a) -> m a Source #
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.
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.
Same as findEntry
, but for Dictionary_
.
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.
:: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) | |
=> Int | Target bucket, key's hash modulo table size |
-> Int | Key's hash |
-> k | Key |
-> v | Value |
-> MutVar (PrimState m) (Dictionary_ (PrimState m) ks k vs v) | MutVar with |
-> Dictionary_ (PrimState m) ks k vs v |
|
-> Int | |
-> m () |
:: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) | |
=> Int | Target bucket, key's hash modulo table size |
-> Int | Key's hash |
-> k | Key |
-> v | Value |
-> MutVar (PrimState m) (Dictionary_ (PrimState m) ks k vs v) | MutVar with |
-> Dictionary_ (PrimState m) ks k vs v |
|
-> m () |
add :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Int -> Int -> Int -> k -> v -> Dictionary_ (PrimState m) ks k vs v -> m () Source #
:: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) | |
=> Dictionary_ (PrimState m) ks k vs v | The original |
-> Int | |
-> Int | Key's hash |
-> k | Key |
-> v | Value |
-> m (Dictionary_ (PrimState m) ks k vs v) |
class DeleteEntry xs where Source #
Instances
DeleteEntry MVector Source # | |
Defined in Data.Vector.Hashtables.Internal | |
DeleteEntry MVector Source # | |
Defined in Data.Vector.Hashtables.Internal | |
DeleteEntry MVector Source # | |
Defined in Data.Vector.Hashtables.Internal |
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.
deleteWithIndex :: (Eq k, MVector ks k, MVector vs v, Hashable k, PrimMonad m, DeleteEntry ks, DeleteEntry vs) => Int -> Int -> Dictionary_ (PrimState m) ks k vs v -> k -> Int -> Int -> m () Source #
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.
lookupIndex :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m (Maybe Int) Source #
O(1) in the best case, O(n) in the worst case. Lookup the index of a key, which is its zero-based index in the sequence sorted by keys. The index is a number from 0 up to, but not including, the size of the dictionary.
length :: (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.
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
.
member :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> k -> m Bool Source #
findWithDefault :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> v -> k -> m v Source #
O(1) in the best case, O(n) in the worst case.
The expression
returns
the value at key findWithDefault
ht def kk
or returns default value def
when the key is not in the dictionary.
upsert :: (MVector ks k, MVector vs v, PrimMonad m, Hashable k, Eq k) => Dictionary (PrimState m) ks k vs v -> (Maybe v -> v) -> k -> m () Source #
O(1) in the best case, O(n) in the worst case.
The expression (
) updates or inserts the value upsert
ht f kx
at k
.
It's a responsibility of MVector
vs
to force evaluation of the updated value.
Unboxed / storable vectors do it automatically. If you use boxed vectors,
consider employing strict ones from
strict-containers
to eliminate potential accumulation of thunks.
let f _ = "c" ht <- fromList [(5,"a"), (3,"b")] upsert ht f 7 toList ht [(3, "b"), (5, "a"), (7, "c")]
ht <- fromList [(5,"a"), (3,"b")] upsert ht f 5 toList ht [(3, "b"), (5, "c")]
alter :: (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 -> Maybe v) -> k -> m () Source #
O(1) in the best case, O(n) in the worst case.
The expression (
) alters the value alter
ht f kx
at k
, or absence thereof.
alter
can be used to insert, delete, or update a value in a Dictionary
.
It's a responsibility of MVector
vs
to force evaluation of the updated value.
Unboxed / storable vectors do it automatically. If you use boxed vectors,
consider employing strict ones from
strict-containers
to eliminate potential accumulation of thunks.
let f _ = Nothing ht <- fromList [(5,"a"), (3,"b")] alter ht f 7 toList ht [(3, "b"), (5, "a")]
ht <- fromList [(5,"a"), (3,"b")] alter ht f 5 toList ht [(3 "b")]
let f _ = Just "c" ht <- fromList [(5,"a"), (3,"b")] alter ht f 7 toList ht [(3, "b"), (5, "a"), (7, "c")]
ht <- fromList [(5,"a"), (3,"b")] alter ht f 5 toList ht [(3, "b"), (5, "c")]
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 :: (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 and intersection
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 :: (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.
List conversions
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.
Extras
getFastRem :: Int -> FastRem Source #