primitive-containers-0.4.0: containers backed by arrays

Safe HaskellNone
LanguageHaskell2010

Data.Map.Unboxed.Unboxed

Contents

Synopsis

Documentation

data Map k v Source #

A map from keys k to values v. The key type and the value type must both have Prim instances.

Instances
(Prim k, Ord k, Prim v) => IsList (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

Associated Types

type Item (Map k v) :: Type #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

(Prim k, Eq k, Prim v, Eq v) => Eq (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

Methods

(==) :: Map k v -> Map k v -> Bool #

(/=) :: Map k v -> Map k v -> Bool #

(Prim k, Ord k, Prim v, Ord v) => Ord (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

Methods

compare :: Map k v -> Map k v -> Ordering #

(<) :: Map k v -> Map k v -> Bool #

(<=) :: Map k v -> Map k v -> Bool #

(>) :: Map k v -> Map k v -> Bool #

(>=) :: Map k v -> Map k v -> Bool #

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

(Prim k, Show k, Prim v, Show v) => Show (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

Methods

showsPrec :: Int -> Map k v -> ShowS #

show :: Map k v -> String #

showList :: [Map k v] -> ShowS #

(Prim k, Ord k, Prim v, Semigroup v) => Semigroup (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

(Prim k, Ord k, Prim v, Semigroup v) => Monoid (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

type Item (Map k v) Source # 
Instance details

Defined in Data.Map.Unboxed.Unboxed

type Item (Map k v) = (k, v)

empty :: Map k v Source #

The empty diet map.

singleton :: (Prim k, Prim v) => k -> v -> Map k v Source #

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

lookup :: (Prim k, Ord k, Prim v) => k -> Map k v -> Maybe v Source #

O(log n) Lookup the value at a key in the map.

size :: Prim v => Map k v -> Int Source #

O(1) The number of elements in the map.

Transform

map :: (Prim k, Prim v, Prim w) => (v -> w) -> Map k v -> Map k w Source #

O(n) Map over the values in the map.

mapMaybe :: (Prim k, Prim v, Prim w) => (v -> Maybe w) -> Map k v -> Map k w Source #

O(n) Drop elements for which the predicate returns Nothing.

mapMaybeWithKey :: (Prim k, Prim v, Prim w) => (k -> v -> Maybe w) -> Map k v -> Map k w Source #

O(n) Drop elements for which the predicate returns Nothing. The predicate is given access to the key.

adjustMany Source #

Arguments

:: (Prim k, Prim v, PrimMonad m, Ord k) 
=> ((k -> (v -> m v) -> m ()) -> m a)

Modification-applying function

-> Map k v

Map

-> m (Map k v, a) 

Update the values at any number of keys. This is done on in a buffer without building intermediate maps. Example use:

adjustMany
  (\adjust -> do
    adjust 2 (\x -> pure (x + 1))
    adjust 3 (\_ -> pure 42)
  ) myMap

This increments by 1 the value associated with key 2. Then, it replaces with 42 the value associated with key 3.

adjustManyInline Source #

Arguments

:: (Prim k, Prim v, PrimMonad m, Ord k) 
=> ((k -> (v -> m v) -> m ()) -> m a)

Modification-applying function

-> Map k v

Map

-> m (Map k v, a) 

This has the same behavior as adjustMany. However, it will be inlined rather than specialized. The can prevent needless boxing in the callback. Use -ddump-simpl and standard profiling techniques to figure out if this function actually helps you.

Folds

foldlWithKey' Source #

Arguments

:: (Prim k, Prim v) 
=> (b -> k -> v -> b)

reduction

-> b

initial accumulator

-> Map k v

map

-> b 

O(n) Left fold over the keys and values with a strict accumulator.

foldrWithKey' Source #

Arguments

:: (Prim k, Prim v) 
=> (k -> v -> b -> b)

reduction

-> b

initial accumulator

-> Map k v

map

-> b 

O(n) Right fold over the keys and values with a strict accumulator.

foldMapWithKey' Source #

Arguments

:: (Monoid b, Prim k, Prim v) 
=> (k -> v -> b)

reduction

-> Map k v

map

-> b 

O(n) Fold over the keys and values of the map with a strict monoidal accumulator. This function does not have left and right variants since the associativity required by a monoid instance means that both variants would always produce the same result.

Monadic Folds

foldlWithKeyM' Source #

Arguments

:: (Monad m, Prim k, Prim v) 
=> (b -> k -> v -> m b)

reduction

-> b

initial accumulator

-> Map k v

map

-> m b 

O(n) Left monadic fold over the keys and values of the map. This fold is strict in the accumulator.

foldrWithKeyM' Source #

Arguments

:: (Monad m, Prim k, Prim v) 
=> (k -> v -> b -> m b)

reduction

-> b

initial accumulator

-> Map k v

map

-> m b 

O(n) Right monadic fold over the keys and values of the map. This fold is strict in the accumulator.

foldlMapWithKeyM' Source #

Arguments

:: (Monad m, Monoid b, Prim k, Prim v) 
=> (k -> v -> m b)

reduction

-> Map k v

map

-> m b 

O(n) Monadic left fold over the keys and values of the map with a strict monoidal accumulator. The monoidal accumulator is appended to the left after each reduction.

foldrMapWithKeyM' Source #

Arguments

:: (Monad m, Monoid b, Prim k, Prim v) 
=> (k -> v -> m b)

reduction

-> Map k v

map

-> m b 

O(n) Monadic right fold over the keys and values of the map with a strict monoidal accumulator. The monoidal accumulator is appended to the right after each reduction.

Traversals

traverseWithKey_ Source #

Arguments

:: (Monad m, Prim k, Prim v) 
=> (k -> v -> m b)

reduction

-> Map k v

map

-> m () 

O(n) Traverse the keys and values of the map from left to right.

List Conversion

toList :: (Prim k, Ord k, Prim v) => Map k v -> [(k, v)] Source #

O(n) A list of key-value pairs in ascending order.

fromList :: (Prim k, Ord k, Prim v) => [(k, v)] -> Map k v Source #

O(n*log n) Create a map from a list of key-value pairs. If the list contains more than one value for the same key, the last value is retained. If the keys in the argument are in nondescending order, this algorithm runs in O(n) time instead.

fromListAppend :: (Prim k, Ord k, Prim v, Semigroup v) => [(k, v)] -> Map k v Source #

O(n*log n) This function has the same behavior as fromList, but it combines values with the Semigroup instances instead of choosing the last occurrence.

fromListN Source #

Arguments

:: (Prim k, Ord k, Prim v) 
=> Int

expected size of resulting Map

-> [(k, v)]

key-value pairs

-> Map k v 

O(n*log n) This function has the same behavior as fromList regardless of whether or not the expected size is accurate. Additionally, negative sizes are handled correctly. The expected size is used as the size of the initially allocated buffer when building the Map. If the keys in the argument are in nondescending order, this algorithm runs in O(n) time.

fromListAppendN Source #

Arguments

:: (Prim k, Ord k, Prim v, Semigroup v) 
=> Int

expected size of resulting Map

-> [(k, v)]

key-value pairs

-> Map k v 

O(n*log n) This function has the same behavior as fromListN, but it combines values with the Semigroup instances instead of choosing the last occurrence.

fromSet :: (Prim k, Prim v) => (k -> v) -> Set k -> Map k v Source #

O(n) Build a map from a set. This function is uses the underlying array that backs the set as the array for the keys. It constructs the values by apply the given function to each key.

fromSetP :: (PrimMonad m, Prim k, Prim v) => (k -> m v) -> Set k -> m (Map k v) Source #

O(n) Build a map from a set. This function is uses the underlying array that backs the set as the array for the keys. It constructs the values by apply the given function to each key. The function can perform primitive monadic effects.

Array Conversion

unsafeFreezeZip :: (Ord k, Prim k, Prim v) => MutablePrimArray s k -> MutablePrimArray s v -> ST s (Map k v) Source #

O(n*log n) Zip an array of keys with an array of values. If they are not the same length, the longer one will be truncated to match the shorter one. This function sorts and deduplicates the array of keys, preserving the last value associated with each key. The argument arrays may not be reused after being passed to this function.

This is by far the fastest way to create a map, since the functions backing it are aggressively specialized. It internally uses a hybrid of mergesort and insertion sort provided by the primitive-sort package. It generates much less garbage than any of the fromList variants.