Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Map k v
- empty :: Map k v
- singleton :: Prim k => k -> v -> Map k v
- lookup :: (Prim k, Ord k) => k -> Map k v -> Maybe v
- size :: Map k v -> Int
- map :: Prim k => (v -> w) -> Map k v -> Map k w
- mapMaybe :: Prim k => (v -> Maybe w) -> Map k v -> Map k w
- mapMaybeWithKey :: Prim k => (k -> v -> Maybe w) -> Map k v -> Map k w
- mapWithKey :: Prim k => (k -> v -> w) -> Map k v -> Map k w
- keys :: Map k v -> Set k
- intersectionWith :: (Prim k, Ord k) => (a -> b -> c) -> Map k a -> Map k b -> Map k c
- intersectionsWith :: (Prim k, Ord k) => (v -> v -> v) -> NonEmpty (Map k v) -> Map k v
- restrict :: (Prim k, Ord k) => Map k v -> Set k -> Map k v
- appendWithKey :: (Prim k, Ord k) => (k -> v -> v -> v) -> Map k v -> Map k v -> Map k v
- foldrWithKey :: Prim k => (k -> v -> b -> b) -> b -> Map k v -> b
- foldlWithKey' :: Prim k => (b -> k -> v -> b) -> b -> Map k v -> b
- foldrWithKey' :: Prim k => (k -> v -> b -> b) -> b -> Map k v -> b
- foldMapWithKey :: (Monoid b, Prim k) => (k -> v -> b) -> Map k v -> b
- foldMapWithKey' :: (Monoid b, Prim k) => (k -> v -> b) -> Map k v -> b
- foldlWithKeyM' :: (Monad m, Prim k) => (b -> k -> v -> m b) -> b -> Map k v -> m b
- foldrWithKeyM' :: (Monad m, Prim k) => (k -> v -> b -> m b) -> b -> Map k v -> m b
- foldlMapWithKeyM' :: (Monad m, Monoid b, Prim k) => (k -> v -> m b) -> Map k v -> m b
- foldrMapWithKeyM' :: (Monad m, Monoid b, Prim k) => (k -> v -> m b) -> Map k v -> m b
- toList :: (Prim k, Ord k) => Map k v -> [(k, v)]
- fromList :: (Prim k, Ord k) => [(k, v)] -> Map k v
- fromListAppend :: (Prim k, Ord k, Semigroup v) => [(k, v)] -> Map k v
- fromListN :: (Prim k, Ord k) => Int -> [(k, v)] -> Map k v
- fromListAppendN :: (Prim k, Ord k, Semigroup v) => Int -> [(k, v)] -> Map k v
- fromSet :: Prim k => (k -> v) -> Set k -> Map k v
- elems :: Map k v -> Array v
- unsafeFreezeZip :: (Ord k, Prim k) => MutablePrimArray s k -> MutableArray s v -> ST s (Map k v)
Documentation
A map from keys k
to values v
. The key type must have a
Prim
instance and the value type is unconstrained.
Instances
Prim k => Functor (Map k) Source # | This fails the functor laws since fmap is strict. |
(Prim k, Ord k) => IsList (Map k v) Source # | |
(Prim k, Eq k, Eq v) => Eq (Map k v) Source # | |
(Prim k, Ord k, Ord v) => Ord (Map k v) Source # | |
(Prim k, Show k, Show v) => Show (Map k v) Source # | |
(Prim k, Ord k, Semigroup v) => Semigroup (Map k v) Source # | |
(Prim k, Ord k, Semigroup v) => Monoid (Map k v) Source # | |
(Prim k, NFData k, NFData v) => NFData (Map k v) Source # | |
Defined in Data.Map.Unboxed.Lifted | |
type Item (Map k v) Source # | |
Defined in Data.Map.Unboxed.Lifted |
lookup :: (Prim k, Ord k) => k -> Map k v -> Maybe v Source #
O(log n) Lookup the value at a key in the map.
mapMaybe :: Prim k => (v -> Maybe w) -> Map k v -> Map k w Source #
O(n) Drop elements for which the predicate returns Nothing
.
mapMaybeWithKey :: Prim k => (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.
mapWithKey :: Prim k => (k -> v -> w) -> Map k v -> Map k w Source #
O(n) Map over the elements with access to their corresponding keys.
intersectionsWith :: (Prim k, Ord k) => (v -> v -> v) -> NonEmpty (Map k v) -> Map k v Source #
Take the intersection of all of the maps, combining elements at equal keys with the provided function. Since intersection of maps lacks an identity, this is provided with a non-empty list.
Folds
O(n) Right fold over the keys and values with a lazy accumulator.
O(n) Left fold over the keys and values with a strict accumulator.
O(n) Right fold over the keys and values with a strict accumulator.
foldMapWithKey :: (Monoid b, Prim k) => (k -> v -> b) -> Map k v -> b Source #
O(n) Fold over the keys and values of the map with a lazy 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.
foldMapWithKey' :: (Monoid b, Prim k) => (k -> v -> b) -> Map k v -> b Source #
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' :: (Monad m, Prim k) => (b -> k -> v -> m b) -> b -> Map k v -> m b Source #
O(n) Left monadic fold over the keys and values of the map. This fold is strict in the accumulator.
foldrWithKeyM' :: (Monad m, Prim k) => (k -> v -> b -> m b) -> b -> Map k v -> m b Source #
O(n) Right monadic fold over the keys and values of the map. This fold is strict in the accumulator.
foldlMapWithKeyM' :: (Monad m, Monoid b, Prim k) => (k -> v -> m b) -> Map k v -> m b Source #
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.
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.
List Conversion
toList :: (Prim k, Ord k) => Map k v -> [(k, v)] Source #
O(n) A list of key-value pairs in ascending order.
fromList :: (Prim k, Ord k) => [(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.
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.
fromSet :: Prim k => (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 applying the given function to each key.
Array Conversion
unsafeFreezeZip :: (Ord k, Prim k) => MutablePrimArray s k -> MutableArray 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.