hashmap-io-0.1.0.0: A Hashmap on io monad.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.IOHashMap

Synopsis

Documentation

data IOHashMap k v Source #

newIOHashMap :: MonadIO m => HashMap k v -> m (IOHashMap k v) Source #

readIOHashMap :: MonadIO m => (HashMap k v -> a) -> IOHashMap k v -> m a Source #

modifyIOHashMap :: MonadIO m => (HashMap k v -> HashMap k v) -> IOHashMap k v -> m () Source #

empty :: MonadIO m => m (IOHashMap k v) Source #

O(1) Construct an empty map.

singleton :: MonadIO m => Hashable k => k -> v -> m (IOHashMap k v) Source #

O(1) Construct a map with a single element.

null :: MonadIO m => IOHashMap k v -> m Bool Source #

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

size :: MonadIO m => IOHashMap k v -> m Int Source #

O(n) Return the number of key-value mappings in this map.

member :: (MonadIO m, Eq k, Hashable k) => k -> IOHashMap k a -> m Bool Source #

O(log n) Return True if the specified key is present in the map, False otherwise.

lookup :: (MonadIO m, Eq k, Hashable k) => k -> IOHashMap k v -> m (Maybe v) Source #

O(log n) Return the value to which the specified key is mapped, or Nothing if this map contains no mapping for the key.

(!?) :: (MonadIO m, Eq k, Hashable k) => IOHashMap k v -> k -> m (Maybe v) Source #

O(log n) Return the value to which the specified key is mapped, or Nothing if this map contains no mapping for the key.

This is a flipped version of lookup.

Since: 0.2.11

findWithDefault Source #

Arguments

:: (MonadIO m, Eq k, Hashable k) 
=> v

Default value to return.

-> k 
-> IOHashMap k v 
-> m v 

O(log n) Return the value to which the specified key is mapped, or the default value if this map contains no mapping for the key.

Since: 0.2.11

(!) :: (MonadIO m, Eq k, Hashable k) => IOHashMap k v -> k -> m v infixl 9 Source #

O(log n) Return the value to which the specified key is mapped. Calls error if this map contains no mapping for the key.

insert :: (MonadIO m, Eq k, Hashable k) => k -> v -> IOHashMap k v -> m () Source #

O(log n) Associate the specified value with the specified key in this map. If this map previously contained a mapping for the key, the old value is replaced.

insertWith :: (MonadIO m, Eq k, Hashable k) => (v -> v -> v) -> k -> v -> IOHashMap k v -> m () Source #

O(log n) Associate the value with the key in this map. If this map previously contained a mapping for the key, the old value is replaced by the result of applying the given function to the new and old value. Example:

insertWith f k v map
  where f new old = new + old

delete :: (MonadIO m, Eq k, Hashable k) => k -> IOHashMap k v -> m () Source #

O(log n) Remove the mapping for the specified key from this map if present.

adjust :: MonadIO m => (Eq k, Hashable k) => (v -> v) -> k -> IOHashMap k v -> m () Source #

O(log n) Adjust the value tied to a given key in this map only if it is present. Otherwise, leave the map alone.

update :: (MonadIO m, Eq k, Hashable k) => (a -> Maybe a) -> k -> IOHashMap k a -> m () Source #

O(log n) The expression (update f k map) updates the value x at k (if it is in the map). If (f x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

alter :: (MonadIO m, Eq k, Hashable k) => (Maybe v -> Maybe v) -> k -> IOHashMap k v -> m () Source #

O(log n) The expression (alter f k map) alters the value x at k, or absence thereof.

alter can be used to insert, delete, or update a value in a map. In short:

lookup k (alter f k m) = f (lookup k m)

foldMapWithKey :: (MonadIO m, Monoid n) => (k -> v -> n) -> IOHashMap k v -> m n Source #

O(n) Reduce the map by applying a function to each element and combining the results with a monoid operation.

foldr :: MonadIO m => (v -> a -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

foldl :: MonadIO m => (a -> v -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator).

foldr' :: MonadIO m => (v -> a -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldl' :: MonadIO m => (a -> v -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldrWithKey' :: MonadIO m => (k -> v -> a -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldlWithKey' :: MonadIO m => (a -> k -> v -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldrWithKey :: MonadIO m => (k -> v -> a -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

foldlWithKey :: MonadIO m => (a -> k -> v -> a) -> a -> IOHashMap k v -> m a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator).

keys :: MonadIO m => IOHashMap k v -> m [k] Source #

O(n) Return a list of this map's keys. The list is produced lazily.

elems :: MonadIO m => IOHashMap k v -> m [v] Source #

O(n) Return a list of this map's values. The list is produced lazily.

toList :: MonadIO m => IOHashMap k v -> m [(k, v)] Source #

O(n) Return a list of this map's elements. The list is produced lazily. The order of its elements is unspecified.

fromList :: (MonadIO m, Eq k, Hashable k) => [(k, v)] -> m (IOHashMap k v) Source #

O(n) Construct a map with the supplied mappings. If the list contains duplicate mappings, the later mappings take precedence.