mini-1.3.0.0: Minimal essentials
Safe HaskellSafe-Inferred
LanguageHaskell2010

Mini.Data.Map

Description

Representation of a structure mapping unique keys to values. The internal structure is an AVL tree.

Synopsis

Type

data Map k a Source #

A map from keys of type k to values of type a.

The internal structure is an AVL tree; a tree that is always height-balanced (the absolute value of the level difference between the left and right subtrees is at most 1).

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 #

Combination

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

\(O(n \log n)\) Map difference (matching only on keys)

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

\(O(n \log n)\) Left-biased map intersection (matching only on keys)

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

\(O(n \log n)\) Left-biased map union (matching only on keys)

Construction

empty :: Map k a Source #

\(O(1)\) The empty map

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

\(O(n \log n)\) From a tail-biased list of (key, value) pairs to a map with bins containing the keys and values

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

\(O(1)\) From a key and a value to a map with a single bin

Conversion

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

\(O(n)\) From a map to a list of (key, value) pairs in key-ascending order

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

\(O(n)\) From a map to a list of (key, value) pairs in key-descending order

Fold

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

\(O(n)\) From a left-associative operation on keys and values, a starting accumulator and a map to a thing

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

\(O(n)\) From a right-associative operation on keys and values, a starting accumulator and a map to a thing

Modification

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

\(O(\log n)\) From an operation, a key and a map to the map adjusted by applying the operation to the value associated with the key

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

\(O(\log n)\) From a key and a map to the map without the key

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

\(O(n)\) From a predicate and a map to the map with values satisfying the predicate

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

\(O(n)\) From a predicate and a map to the map with keys and values satisfying the predicate

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

\(O(\log n)\) From a key, a value and a map to the map including a bin containing the key and the value

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

\(O(\log n)\) From an operation, a key and a map to the map updated by applying the operation to the value associated with the key (setting if Just, deleting if Nothing)

Query

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

\(O(n \log n)\) From a map and another map to whether the former is a submap of the latter (matching on keys and values)

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

\(O(\log n)\) From a key and a map to the value associated with the key in the map

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

\(O(\log n)\) From a map to the value associated with the maximum key in the map

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

\(O(\log n)\) From a map to the value associated with the minimum key in the map

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

\(O(\log n)\) From a key and a map to whether the key is in the map

null :: Map k a -> Bool Source #

\(O(1)\) From a map to whether the map is empty

size :: Map k a -> Int Source #

\(O(n)\) From a map to the size of the map

Traversal

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

\(O(n)\) From a lifting operation on keys and values and a map to a lifted map

Validation

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

\(O(n)\) From a map to whether its internal structure is valid, i.e. height-balanced and ordered