unordered-intmap-0.1.0.0: A specialization of `HashMap Int v`

Safe HaskellNone
LanguageHaskell2010

Data.Unordered.IntMap

Contents

Synopsis

Documentation

data UnorderedIntMap v Source #

A map from (possibly newtyped) Int keys to values. A map cannot contain duplicate keys; each key can map to at most one value.

Instances

Functor UnorderedIntMap Source # 

Methods

fmap :: (a -> b) -> UnorderedIntMap a -> UnorderedIntMap b #

(<$) :: a -> UnorderedIntMap b -> UnorderedIntMap a #

Foldable UnorderedIntMap Source # 

Methods

fold :: Monoid m => UnorderedIntMap m -> m #

foldMap :: Monoid m => (a -> m) -> UnorderedIntMap a -> m #

foldr :: (a -> b -> b) -> b -> UnorderedIntMap a -> b #

foldr' :: (a -> b -> b) -> b -> UnorderedIntMap a -> b #

foldl :: (b -> a -> b) -> b -> UnorderedIntMap a -> b #

foldl' :: (b -> a -> b) -> b -> UnorderedIntMap a -> b #

foldr1 :: (a -> a -> a) -> UnorderedIntMap a -> a #

foldl1 :: (a -> a -> a) -> UnorderedIntMap a -> a #

toList :: UnorderedIntMap a -> [a] #

null :: UnorderedIntMap a -> Bool #

length :: UnorderedIntMap a -> Int #

elem :: Eq a => a -> UnorderedIntMap a -> Bool #

maximum :: Ord a => UnorderedIntMap a -> a #

minimum :: Ord a => UnorderedIntMap a -> a #

sum :: Num a => UnorderedIntMap a -> a #

product :: Num a => UnorderedIntMap a -> a #

Traversable UnorderedIntMap Source # 

Methods

traverse :: Applicative f => (a -> f b) -> UnorderedIntMap a -> f (UnorderedIntMap b) #

sequenceA :: Applicative f => UnorderedIntMap (f a) -> f (UnorderedIntMap a) #

mapM :: Monad m => (a -> m b) -> UnorderedIntMap a -> m (UnorderedIntMap b) #

sequence :: Monad m => UnorderedIntMap (m a) -> m (UnorderedIntMap a) #

Eq1 UnorderedIntMap Source # 

Methods

liftEq :: (a -> b -> Bool) -> UnorderedIntMap a -> UnorderedIntMap b -> Bool #

Ord1 UnorderedIntMap Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> UnorderedIntMap a -> UnorderedIntMap b -> Ordering #

Read1 UnorderedIntMap Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (UnorderedIntMap a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [UnorderedIntMap a] #

Show1 UnorderedIntMap Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UnorderedIntMap a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UnorderedIntMap a] -> ShowS #

IsList (UnorderedIntMap v) Source # 
Eq v => Eq (UnorderedIntMap v) Source # 
Ord v => Ord (UnorderedIntMap v) Source #

The order is total.

Read e => Read (UnorderedIntMap e) Source # 
Show v => Show (UnorderedIntMap v) Source # 
Semigroup (UnorderedIntMap v) Source # 
Monoid (UnorderedIntMap v) Source # 
NFData v => NFData (UnorderedIntMap v) Source # 

Methods

rnf :: UnorderedIntMap v -> () #

type Item (UnorderedIntMap v) Source # 
type Item (UnorderedIntMap v) = (Int, v)

data Leaf v Source #

A set of values. A set cannot contain duplicate values.

Constructors

L !Int v 

Instances

Eq v => Eq (Leaf v) Source # 

Methods

(==) :: Leaf v -> Leaf v -> Bool #

(/=) :: Leaf v -> Leaf v -> Bool #

NFData v => NFData (Leaf v) Source # 

Methods

rnf :: Leaf v -> () #

Construction

empty :: UnorderedIntMap v Source #

O(1) Construct an empty map.

singleton :: Coercible key Int => key -> v -> UnorderedIntMap v Source #

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

Basic interface

null :: UnorderedIntMap v -> Bool Source #

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

size :: UnorderedIntMap v -> Int Source #

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

member :: Coercible key Int => key -> UnorderedIntMap a -> Bool Source #

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

lookup :: Coercible key Int => key -> UnorderedIntMap v -> 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.

lookupDefault Source #

Arguments

:: Coercible key Int 
=> v

Default value to return.

-> key 
-> UnorderedIntMap v 
-> 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.

(!) :: Coercible key Int => UnorderedIntMap v -> key -> 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 :: Coercible key Int => key -> v -> UnorderedIntMap v -> UnorderedIntMap v 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 :: Coercible key Int => (v -> v -> v) -> key -> v -> UnorderedIntMap v -> UnorderedIntMap v 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

unsafeInsert :: Coercible key Int => key -> v -> UnorderedIntMap v -> UnorderedIntMap v Source #

In-place update version of insert

delete :: Coercible key Int => key -> UnorderedIntMap v -> UnorderedIntMap v Source #

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

adjust :: Coercible key Int => (v -> v) -> key -> UnorderedIntMap v -> UnorderedIntMap v 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 :: Coercible key Int => (a -> Maybe a) -> key -> UnorderedIntMap a -> UnorderedIntMap a Source #

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

alter :: Coercible key Int => (Maybe v -> Maybe v) -> key -> UnorderedIntMap v -> UnorderedIntMap v 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).

Combine

Union

union :: UnorderedIntMap v -> UnorderedIntMap v -> UnorderedIntMap v Source #

O(n+m) 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 :: forall v. (v -> v -> v) -> UnorderedIntMap v -> UnorderedIntMap v -> UnorderedIntMap v Source #

O(n+m) The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.

unionWithKey :: Coercible key Int => (key -> v -> v -> v) -> UnorderedIntMap v -> UnorderedIntMap v -> UnorderedIntMap v Source #

O(n+m) The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.

unions :: [UnorderedIntMap v] -> UnorderedIntMap v Source #

Construct a set containing all elements from a list of sets.

Transformations

map :: forall v1 v2. (v1 -> v2) -> UnorderedIntMap v1 -> UnorderedIntMap v2 Source #

O(n) Transform this map by applying a function to every value.

mapWithKey :: Coercible key Int => (key -> v1 -> v2) -> UnorderedIntMap v1 -> UnorderedIntMap v2 Source #

O(n) Transform this map by applying a function to every value.

traverseWithKey :: (Coercible key Int, Applicative f) => (key -> v1 -> f v2) -> UnorderedIntMap v1 -> f (UnorderedIntMap v2) Source #

O(n) Transform this map by accumulating an Applicative result from every value.

Difference and intersection

difference :: UnorderedIntMap v -> UnorderedIntMap w -> UnorderedIntMap v Source #

O(n*log m) Difference of two maps. Return elements of the first map not existing in the second.

differenceWith :: (v -> w -> Maybe v) -> UnorderedIntMap v -> UnorderedIntMap w -> UnorderedIntMap v Source #

O(n*log m) 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 :: UnorderedIntMap v -> UnorderedIntMap w -> UnorderedIntMap v Source #

O(n*log m) Intersection of two maps. Return elements of the first map for keys existing in the second.

intersectionWith :: (v1 -> v2 -> v3) -> UnorderedIntMap v1 -> UnorderedIntMap v2 -> UnorderedIntMap v3 Source #

O(n+m) 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 :: Coercible key Int => (key -> v1 -> v2 -> v3) -> UnorderedIntMap v1 -> UnorderedIntMap v2 -> UnorderedIntMap v3 Source #

O(n+m) Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.

Folds

foldl' :: (a -> v -> a) -> a -> UnorderedIntMap v -> 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 before using the result in the next application. This function is strict in the starting value.

foldlWithKey' :: (a -> Int -> v -> a) -> a -> UnorderedIntMap v -> 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 before using the result in the next application. This function is strict in the starting value.

foldr :: (v -> a -> a) -> a -> UnorderedIntMap v -> 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).

foldrWithKey :: (Int -> v -> a -> a) -> a -> UnorderedIntMap v -> 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).

Filter

mapMaybe :: (v1 -> Maybe v2) -> UnorderedIntMap v1 -> UnorderedIntMap v2 Source #

O(n) Transform this map by applying a function to every value and retaining only some of them.

mapMaybeWithKey :: (Int -> v1 -> Maybe v2) -> UnorderedIntMap v1 -> UnorderedIntMap v2 Source #

O(n) Transform this map by applying a function to every value and retaining only some of them.

filter :: (v -> Bool) -> UnorderedIntMap v -> UnorderedIntMap v Source #

O(n) Filter this map by retaining only elements which values satisfy a predicate.

filterWithKey :: forall v. (Int -> v -> Bool) -> UnorderedIntMap v -> UnorderedIntMap v Source #

O(n) Filter this map by retaining only elements satisfying a predicate.

Conversions

keys :: UnorderedIntMap v -> [Int] Source #

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

elems :: forall v. UnorderedIntMap v -> [v] Source #

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

Lists

toList :: UnorderedIntMap v -> [(Int, 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 :: [(Int, v)] -> UnorderedIntMap v Source #

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

fromListWith :: Coercible key Int => (v -> v -> v) -> [(key, v)] -> UnorderedIntMap v Source #

O(n*log n) Construct a map from a list of elements. Uses the provided function to merge duplicate entries.

mask :: Int -> Shift -> Bitmap Source #

index :: Int -> Shift -> Int Source #

Mask out the bitsPerSubkey bits used for indexing at this level of the tree.

fullNodeMask :: Bitmap Source #

A bitmask with the bitsPerSubkey least significant bits set.

two :: Shift -> Int -> v -> Int -> v -> ST s (UnorderedIntMap v) Source #

Create a map from two key-value pairs which hashes don't collide.

unionArrayBy :: (a -> a -> a) -> Bitmap -> Bitmap -> SmallArray a -> SmallArray a -> SmallArray a Source #

Strict in the result of f.

update16 :: SmallArray e -> Int -> e -> SmallArray e Source #

O(n) Update the element at the given position in this array.

update16M :: SmallArray e -> Int -> e -> ST s (SmallArray e) Source #

O(n) Update the element at the given position in this array.

update16With' :: SmallArray e -> Int -> (e -> e) -> SmallArray e Source #

O(n) Update the element at the given position in this array, by applying a function to it.

updateOrConcatWith :: forall v. (v -> v -> v) -> SmallArray (Leaf v) -> SmallArray (Leaf v) -> SmallArray (Leaf v) Source #

updateOrConcatWithKey :: (Int -> v -> v -> v) -> SmallArray (Leaf v) -> SmallArray (Leaf v) -> SmallArray (Leaf v) Source #

filterMapAux :: forall v1 v2. (UnorderedIntMap v1 -> Maybe (UnorderedIntMap v2)) -> UnorderedIntMap v1 -> UnorderedIntMap v2 Source #

Common implementation for filterWithKey and mapMaybeWithKey, allowing the former to former to reuse terms.