mini-1.3.0.1: Minimal essentials
Safe HaskellSafe-Inferred
LanguageHaskell2010

Mini.Data.Map

Description

A structure mapping unique keys to values

Synopsis

Type

data Map k a Source #

A map from keys k to values a, internally structured as an AVL tree

Instances

Instances details
Foldable (Map k) Source # 
Instance details

Defined in Mini.Data.Map

Methods

fold :: Monoid m => Map k m -> m #

foldMap :: Monoid m => (a -> m) -> Map k a -> m #

foldMap' :: Monoid m => (a -> m) -> Map k a -> m #

foldr :: (a -> b -> b) -> b -> Map k a -> b #

foldr' :: (a -> b -> b) -> b -> Map k a -> b #

foldl :: (b -> a -> b) -> b -> Map k a -> b #

foldl' :: (b -> a -> b) -> b -> Map k a -> b #

foldr1 :: (a -> a -> a) -> Map k a -> a #

foldl1 :: (a -> a -> a) -> Map k a -> a #

toList :: Map k a -> [a] #

null :: Map k a -> Bool #

length :: Map k a -> Int #

elem :: Eq a => a -> Map k a -> Bool #

maximum :: Ord a => Map k a -> a #

minimum :: Ord a => Map k a -> a #

sum :: Num a => Map k a -> a #

product :: Num a => Map k a -> a #

Traversable (Map k) Source # 
Instance details

Defined in Mini.Data.Map

Methods

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

sequenceA :: Applicative f => Map k (f a) -> f (Map k a) #

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

sequence :: Monad m => Map k (m a) -> m (Map k a) #

Functor (Map k) Source # 
Instance details

Defined in Mini.Data.Map

Methods

fmap :: (a -> b) -> Map k a -> Map k b #

(<$) :: a -> Map k b -> Map k a #

Ord k => Monoid (Map k a) Source # 
Instance details

Defined in Mini.Data.Map

Methods

mempty :: Map k a #

mappend :: Map k a -> Map k a -> Map k a #

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

Ord k => Semigroup (Map k a) Source # 
Instance details

Defined in Mini.Data.Map

Methods

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

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

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

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

Defined in Mini.Data.Map

Methods

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

show :: Map k a -> String #

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

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

Defined in Mini.Data.Map

Methods

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

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

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

Defined in Mini.Data.Map

Methods

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

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

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

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

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

max :: Map k a -> Map k a -> Map k a #

min :: Map k a -> Map k a -> Map k a #

Construction

empty :: Map k a Source #

O(1) The empty map

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

O(n log n) Make a map from a tail-biased list of (key, value) pairs

singleton :: k -> a -> Map k a Source #

O(1) Make a map with a single bin

Combination

difference :: Ord k => Map k a -> Map k b -> Map k a Source #

O(n log n) Subtract a map by another via key matching

intersection :: Ord k => Map k a -> Map k b -> Map k a Source #

O(n log n) Intersect a map with another via left-biased key matching

union :: Ord k => Map k a -> Map k a -> Map k a Source #

O(n log n) Unite a map with another via left-biased key matching

Conversion

toAscList :: Map k a -> [(k, a)] Source #

O(n) Turn a map into a list of (key, value) pairs in ascending order

toDescList :: Map k a -> [(k, a)] Source #

O(n) Turn a map into a list of (key, value) pairs in descending order

Fold

foldlWithKey :: (b -> k -> a -> b) -> b -> Map k a -> b Source #

O(n) Reduce a map with a left-associative operation and an accumulator

foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b Source #

O(n) Reduce a map with a right-associative operation and an accumulator

Modification

adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a Source #

O(log n) Adjust with an operation the value of a key in a map

delete :: Ord k => k -> Map k a -> Map k a Source #

O(log n) Delete a key from a map

filter :: Ord k => (a -> Bool) -> Map k a -> Map k a Source #

O(n) Keep the bins whose values satisfy a predicate

filterWithKey :: Ord k => (k -> a -> Bool) -> Map k a -> Map k a Source #

O(n) Keep the bins whose keys and values satisfy a predicate

insert :: Ord k => k -> a -> Map k a -> Map k a Source #

O(log n) Insert a key and its value into a map, overwriting if present

update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a Source #

O(log n) Modify the value of a key or delete its bin with an operation

Query

isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool Source #

O(n log n) Check whether the bins of one map exist in the other

lookup :: Ord k => k -> Map k a -> Maybe a Source #

O(log n) Fetch the value of a key in a map, or Nothing if absent

lookupMax :: Map k a -> Maybe a Source #

O(log n) Fetch the maximum value, or Nothing if the map is empty

lookupMin :: Map k a -> Maybe a Source #

O(log n) Fetch the minimum value, or Nothing if the map is empty

member :: Ord k => k -> Map k a -> Bool Source #

O(log n) Check whether a key is in a map

null :: Map k a -> Bool Source #

O(1) Check whether a map is empty

size :: Map k a -> Int Source #

O(n) Get the size of a map

Traversal

traverseWithKey :: Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b) Source #

O(n) Lift a map with a lifting operation on keys and values

Validation

valid :: Ord k => Map k a -> Bool Source #

O(n) Check whether a map is internally height-balanced and ordered