vector-hashtables-0.1.1.0: Efficient vector-based mutable hashtables implementation.
Copyright(c) klapaucius swamp_agr 2016-2021
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Hashtables

Description

 
Synopsis

Documentation

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.

Constructors

DRef 

Fields

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.

Constructors

FrozenDictionary 

Fields

Instances

Instances details
(Eq (ks k), Eq (vs v)) => Eq (FrozenDictionary ks k vs v) Source # 
Instance details

Defined in Data.Vector.Hashtables.Internal

Methods

(==) :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Bool #

(/=) :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Bool #

(Ord (ks k), Ord (vs v)) => Ord (FrozenDictionary ks k vs v) Source # 
Instance details

Defined in Data.Vector.Hashtables.Internal

Methods

compare :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Ordering #

(<) :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Bool #

(<=) :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Bool #

(>) :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Bool #

(>=) :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> Bool #

max :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v #

min :: FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v -> FrozenDictionary ks k vs v #

(Show (ks k), Show (vs v)) => Show (FrozenDictionary ks k vs v) Source # 
Instance details

Defined in Data.Vector.Hashtables.Internal

Methods

showsPrec :: Int -> FrozenDictionary ks k vs v -> ShowS #

show :: FrozenDictionary ks k vs v -> String #

showList :: [FrozenDictionary ks k vs v] -> ShowS #

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.

Constructors

Dictionary 

Fields

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

null :: (MVector ks k, PrimMonad m) => Dictionary (PrimState m) ks k vs v -> m Bool Source #

O(1) Return True if dictionary is empty, False otherwise.

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.

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 (alter ht f k) alters the value x at k, or absence thereof. alter can be used to insert, delete, or update a value in a Dictionary.

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 (alterM ht f k) alters the value x 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 (Just y), the element is updated with a new value y.

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.