Z-Data-0.8.3.0: Array, vector and text
Copyright(c) Dong Han 2017-2019
(c) Tao He 2018-2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Vector.FlatIntMap

Description

This module provides a simple int key value map based on sorted vector and binary search. It's particularly suitable for small sized key value collections such as deserializing intermediate representation. But can also used in various place where insertion and deletion is rare but require fast lookup.

Synopsis

FlatIntMap backed by sorted vector

data FlatIntMap v Source #

Instances

Instances details
Functor FlatIntMap Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Methods

fmap :: (a -> b) -> FlatIntMap a -> FlatIntMap b #

(<$) :: a -> FlatIntMap b -> FlatIntMap a #

Foldable FlatIntMap Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Methods

fold :: Monoid m => FlatIntMap m -> m #

foldMap :: Monoid m => (a -> m) -> FlatIntMap a -> m #

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

foldr :: (a -> b -> b) -> b -> FlatIntMap a -> b #

foldr' :: (a -> b -> b) -> b -> FlatIntMap a -> b #

foldl :: (b -> a -> b) -> b -> FlatIntMap a -> b #

foldl' :: (b -> a -> b) -> b -> FlatIntMap a -> b #

foldr1 :: (a -> a -> a) -> FlatIntMap a -> a #

foldl1 :: (a -> a -> a) -> FlatIntMap a -> a #

toList :: FlatIntMap a -> [a] #

null :: FlatIntMap a -> Bool #

length :: FlatIntMap a -> Int #

elem :: Eq a => a -> FlatIntMap a -> Bool #

maximum :: Ord a => FlatIntMap a -> a #

minimum :: Ord a => FlatIntMap a -> a #

sum :: Num a => FlatIntMap a -> a #

product :: Num a => FlatIntMap a -> a #

Traversable FlatIntMap Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Methods

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

sequenceA :: Applicative f => FlatIntMap (f a) -> f (FlatIntMap a) #

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

sequence :: Monad m => FlatIntMap (m a) -> m (FlatIntMap a) #

Eq v => Eq (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Methods

(==) :: FlatIntMap v -> FlatIntMap v -> Bool #

(/=) :: FlatIntMap v -> FlatIntMap v -> Bool #

Ord v => Ord (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Show v => Show (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Semigroup (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Monoid (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Arbitrary v => Arbitrary (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

CoArbitrary v => CoArbitrary (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Methods

coarbitrary :: FlatIntMap v -> Gen b -> Gen b #

NFData v => NFData (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

Methods

rnf :: FlatIntMap v -> () #

Print v => Print (FlatIntMap v) Source # 
Instance details

Defined in Z.Data.Vector.FlatIntMap

JSON a => JSON (FlatIntMap a) Source # 
Instance details

Defined in Z.Data.JSON.Base

empty :: FlatIntMap v Source #

O(1) empty flat map.

map' :: (v -> v') -> FlatIntMap v -> FlatIntMap v' Source #

imap' :: (Int -> v -> v') -> FlatIntMap v -> FlatIntMap v' Source #

pack :: [IPair v] -> FlatIntMap v Source #

O(N*logN) Pack list of key values, on key duplication prefer left one.

packN :: Int -> [IPair v] -> FlatIntMap v Source #

O(N*logN) Pack list of key values with suggested size, on key duplication prefer left one.

packR :: [IPair v] -> FlatIntMap v Source #

O(N*logN) Pack list of key values, on key duplication prefer right one.

packRN :: Int -> [IPair v] -> FlatIntMap v Source #

O(N*logN) Pack list of key values with suggested size, on key duplication prefer right one.

unpack :: FlatIntMap v -> [IPair v] Source #

O(N) Unpack key value pairs to a list sorted by keys in ascending order.

This function works with foldr/build fusion in base.

unpackR :: FlatIntMap v -> [IPair v] Source #

O(N) Unpack key value pairs to a list sorted by keys in descending order.

This function works with foldr/build fusion in base.

packVector :: Vector (IPair v) -> FlatIntMap v Source #

O(N*logN) Pack vector of key values, on key duplication prefer left one.

packVectorR :: Vector (IPair v) -> FlatIntMap v Source #

O(N*logN) Pack vector of key values, on key duplication prefer right one.

lookup :: Int -> FlatIntMap v -> Maybe v Source #

O(logN) Binary search on flat map.

delete :: Int -> FlatIntMap v -> FlatIntMap v Source #

O(N) Delete a key value pair by key.

insert :: Int -> v -> FlatIntMap v -> FlatIntMap v Source #

O(N) Insert new key value into map, replace old one if key exists.

adjust' :: (v -> v) -> Int -> FlatIntMap v -> FlatIntMap v Source #

O(N) Modify a value by key.

The value is evaluated to WHNF before writing into map.

merge :: forall v. FlatIntMap v -> FlatIntMap v -> FlatIntMap v Source #

O(n+m) Merge two FlatIntMap, prefer right value on key duplication.

mergeWithKey' :: forall v. (Int -> v -> v -> v) -> FlatIntMap v -> FlatIntMap v -> FlatIntMap v Source #

O(n+m) Merge two FlatIntMap with a merge function.

fold and traverse

foldrWithKey :: (Int -> v -> a -> a) -> a -> FlatIntMap v -> a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

During folding k is in descending order.

foldrWithKey' :: (Int -> v -> a -> a) -> a -> FlatIntMap v -> a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

During folding Int is in descending order.

foldlWithKey :: (a -> Int -> v -> a) -> a -> FlatIntMap v -> a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

During folding Int is in ascending order.

foldlWithKey' :: (a -> Int -> v -> a) -> a -> FlatIntMap v -> a Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

During folding Int is in ascending order.

traverseWithKey :: Applicative t => (Int -> a -> t b) -> FlatIntMap a -> t (FlatIntMap b) Source #

O(n).

traverseWithKey f s == pack <$> traverse ((k, v) -> (,) k <$> f k v) (unpack m) That is, behaves exactly like a regular traverse except that the traversing function also has access to the key associated with a value.

binary search on vectors

binarySearch :: Vector (IPair v) -> Int -> Either Int Int Source #

Find the key's index in the vector slice, if key exists return Right, otherwise Left, i.e. the insert index

This function only works on ascending sorted vectors.