primitive-containers-0.2.0

Safe HaskellNone
LanguageHaskell2010

Data.Map.Unboxed.Unlifted

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, PrimUnlifted v) => IsList (Map k v) Source # 

Associated Types

type Item (Map k v) :: * #

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, PrimUnlifted v, Eq v) => Eq (Map k v) Source # 

Methods

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

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

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

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, PrimUnlifted v, Show v) => Show (Map k v) Source # 

Methods

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

show :: Map k v -> String #

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

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

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, PrimUnlifted v, Semigroup v) => Monoid (Map k v) Source # 

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 # 
type Item (Map k v) = (k, v)

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

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

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

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

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

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

List Conversion

fromList :: (Prim k, Ord k, PrimUnlifted 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, PrimUnlifted 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, PrimUnlifted 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, PrimUnlifted 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.