Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Map k v = Map (Map Array Array k v)
- empty :: Map k v
- singleton :: k -> v -> Map k v
- lookup :: Ord k => k -> Map k v -> Maybe v
- size :: Map k v -> Int
- map :: (v -> w) -> Map k v -> Map k w
- mapMaybe :: (v -> Maybe w) -> Map k v -> Map k w
- mapMaybeWithKey :: (k -> v -> Maybe w) -> Map k v -> Map k w
- appendWithKey :: Ord k => (k -> v -> v -> v) -> Map k v -> Map k v -> Map k v
- union :: Ord k => Map k v -> Map k v -> Map k v
- foldlWithKey' :: (b -> k -> v -> b) -> b -> Map k v -> b
- foldrWithKey' :: (k -> v -> b -> b) -> b -> Map k v -> b
- foldMapWithKey' :: Monoid b => (k -> v -> b) -> Map k v -> b
- foldlWithKeyM' :: Monad m => (b -> k -> v -> m b) -> b -> Map k v -> m b
- foldrWithKeyM' :: Monad m => (k -> v -> b -> m b) -> b -> Map k v -> m b
- foldlMapWithKeyM' :: (Monad m, Monoid b) => (k -> v -> m b) -> Map k v -> m b
- foldrMapWithKeyM' :: (Monad m, Monoid b) => (k -> v -> m b) -> Map k v -> m b
- toList :: Ord k => Map k v -> [(k, v)]
- fromList :: Ord k => [(k, v)] -> Map k v
- fromListAppend :: (Ord k, Semigroup v) => [(k, v)] -> Map k v
- fromListN :: Ord k => Int -> [(k, v)] -> Map k v
- fromListAppendN :: (Ord k, Semigroup v) => Int -> [(k, v)] -> Map k v
- fromSet :: (k -> v) -> Set k -> Map k v
- keys :: Map k v -> Set k
- elems :: Map k v -> Array v
Documentation
A map from keys k
to values v
.
Instances
Functor (Map k) Source # | |
Ord k => IsList (Map k v) Source # | |
(Eq k, Eq v) => Eq (Map k v) Source # | |
(Ord k, Ord v) => Ord (Map k v) Source # | |
(Show k, Show v) => Show (Map k v) Source # | |
(Ord k, Semigroup v) => Semigroup (Map k v) Source # | |
(Ord k, Semigroup v) => Monoid (Map k v) Source # | |
type Item (Map k v) Source # | |
Defined in Data.Map.Lifted.Lifted |
mapMaybe :: (v -> Maybe w) -> Map k v -> Map k w Source #
O(n) Drop elements for which the predicate returns Nothing
.
mapMaybeWithKey :: (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.
union :: Ord k => Map k v -> Map k v -> Map k v Source #
O(n+m) The expression (
) takes the left-biased union
of union
t1 t2t1
and t2
. It prefers t1
when duplicate keys are encountered.
Folds
:: (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.
:: (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.
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
O(n) Left monadic fold over the keys and values of the map. This fold is strict in the accumulator.
O(n) Right monadic fold over the keys and values of the map. This fold is strict in the accumulator.
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
fromList :: 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.