ordered-containers-0.2.2: Set- and Map-like types that remember the order elements were inserted

Safe HaskellSafe
LanguageHaskell98

Data.Map.Ordered.Strict

Contents

Description

An OMap behaves much like a Map, with mostly the same asymptotics, but also remembers the order that keys were inserted. All operations whose asymptotics are worse than Map have documentation saying so.

Synopsis

Documentation

data OMap k v Source #

Instances
Functor (OMap k) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

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

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

Foldable (OMap k) Source #

Values are produced in insertion order, not key order.

Instance details

Defined in Data.Map.Ordered.Internal

Methods

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

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

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

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

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

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

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

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

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

null :: OMap k a -> Bool #

length :: OMap k a -> Int #

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

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

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

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

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

Ord k => Traversable (OMap k) Source #

Values are traversed in insertion order, not key order.

O(n*log(n)) where n is the size of the map.

Instance details

Defined in Data.Map.Ordered.Internal

Methods

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

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

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

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

(Eq k, Eq v) => Eq (OMap k v) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

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

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

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

Defined in Data.Map.Ordered.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OMap k a -> c (OMap k a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OMap k a) #

toConstr :: OMap k a -> Constr #

dataTypeOf :: OMap k a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (OMap k a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OMap k a)) #

gmapT :: (forall b. Data b => b -> b) -> OMap k a -> OMap k a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OMap k a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OMap k a -> r #

gmapQ :: (forall d. Data d => d -> u) -> OMap k a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OMap k a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OMap k a -> m (OMap k a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OMap k a -> m (OMap k a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OMap k a -> m (OMap k a) #

(Ord k, Ord v) => Ord (OMap k v) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

compare :: OMap k v -> OMap k v -> Ordering #

(<) :: OMap k v -> OMap k v -> Bool #

(<=) :: OMap k v -> OMap k v -> Bool #

(>) :: OMap k v -> OMap k v -> Bool #

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

max :: OMap k v -> OMap k v -> OMap k v #

min :: OMap k v -> OMap k v -> OMap k v #

(Ord k, Read k, Read v) => Read (OMap k v) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

readsPrec :: Int -> ReadS (OMap k v) #

readList :: ReadS [OMap k v] #

readPrec :: ReadPrec (OMap k v) #

readListPrec :: ReadPrec [OMap k v] #

(Show k, Show v) => Show (OMap k v) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

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

show :: OMap k v -> String #

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

(Ord k, Semigroup v) => Semigroup (Bias R (OMap k v)) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

(<>) :: Bias R (OMap k v) -> Bias R (OMap k v) -> Bias R (OMap k v) #

sconcat :: NonEmpty (Bias R (OMap k v)) -> Bias R (OMap k v) #

stimes :: Integral b => b -> Bias R (OMap k v) -> Bias R (OMap k v) #

(Ord k, Semigroup v) => Semigroup (Bias L (OMap k v)) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

(<>) :: Bias L (OMap k v) -> Bias L (OMap k v) -> Bias L (OMap k v) #

sconcat :: NonEmpty (Bias L (OMap k v)) -> Bias L (OMap k v) #

stimes :: Integral b => b -> Bias L (OMap k v) -> Bias L (OMap k v) #

(Ord k, Monoid v) => Monoid (Bias R (OMap k v)) Source #

Empty maps and map union. When combining two sets that share elements, the indices of the right argument are preferred, and the values are combined with mappend.

See the asymptotics of unionWithR.

Instance details

Defined in Data.Map.Ordered.Internal

Methods

mempty :: Bias R (OMap k v) #

mappend :: Bias R (OMap k v) -> Bias R (OMap k v) -> Bias R (OMap k v) #

mconcat :: [Bias R (OMap k v)] -> Bias R (OMap k v) #

(Ord k, Monoid v) => Monoid (Bias L (OMap k v)) Source #

Empty maps and map union. When combining two sets that share elements, the indices of the left argument are preferred, and the values are combined with mappend.

See the asymptotics of unionWithL.

Instance details

Defined in Data.Map.Ordered.Internal

Methods

mempty :: Bias L (OMap k v) #

mappend :: Bias L (OMap k v) -> Bias L (OMap k v) -> Bias L (OMap k v) #

mconcat :: [Bias L (OMap k v)] -> Bias L (OMap k v) #

Trivial maps

singleton :: (k, v) -> OMap k v Source #

Insertion

Conventions:

  • The open side of an angle bracket points to an OMap
  • The pipe appears on the side whose indices take precedence if both sides contain the same key
  • The left argument's indices are lower than the right argument's indices
  • If both sides contain the same key, the tuple's value wins

(<|) :: Ord k => (,) k v -> OMap k v -> OMap k v infixr 5 Source #

(|<) :: Ord k => (,) k v -> OMap k v -> OMap k v infixr 5 Source #

(>|) :: Ord k => OMap k v -> (,) k v -> OMap k v infixl 5 Source #

(|>) :: Ord k => OMap k v -> (,) k v -> OMap k v infixl 5 Source #

(<>|) :: Ord k => OMap k v -> OMap k v -> OMap k v infixr 6 Source #

When a key occurs in both maps, prefer the value from the first map.

See asymptotics of unionWithR.

(|<>) :: Ord k => OMap k v -> OMap k v -> OMap k v infixr 6 Source #

When a key occurs in both maps, prefer the value from the first map.

See asymptotics of unionWithL.

unionWithL :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v Source #

Take the union. The first OMap 's argument's indices are lower than the second. If a key appears in both maps, the first argument's index takes precedence, and the supplied function is used to combine the values.

O(r*log(r)) where r is the size of the result

unionWithR :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v Source #

Take the union. The first OMap 's argument's indices are lower than the second. If a key appears in both maps, the second argument's index takes precedence, and the supplied function is used to combine the values.

O(r*log(r)) where r is the size of the result

newtype Bias (dir :: IndexPreference) a Source #

A newtype to hand a Monoid instance on. The phantom first parameter tells whether mappend will prefer the indices of its first or second argument if there are shared elements in both.

Constructors

Bias 

Fields

Instances
Functor (Bias dir) Source # 
Instance details

Defined in Data.Map.Util

Methods

fmap :: (a -> b) -> Bias dir a -> Bias dir b #

(<$) :: a -> Bias dir b -> Bias dir a #

Foldable (Bias dir) Source # 
Instance details

Defined in Data.Map.Util

Methods

fold :: Monoid m => Bias dir m -> m #

foldMap :: Monoid m => (a -> m) -> Bias dir a -> m #

foldr :: (a -> b -> b) -> b -> Bias dir a -> b #

foldr' :: (a -> b -> b) -> b -> Bias dir a -> b #

foldl :: (b -> a -> b) -> b -> Bias dir a -> b #

foldl' :: (b -> a -> b) -> b -> Bias dir a -> b #

foldr1 :: (a -> a -> a) -> Bias dir a -> a #

foldl1 :: (a -> a -> a) -> Bias dir a -> a #

toList :: Bias dir a -> [a] #

null :: Bias dir a -> Bool #

length :: Bias dir a -> Int #

elem :: Eq a => a -> Bias dir a -> Bool #

maximum :: Ord a => Bias dir a -> a #

minimum :: Ord a => Bias dir a -> a #

sum :: Num a => Bias dir a -> a #

product :: Num a => Bias dir a -> a #

Traversable (Bias dir) Source # 
Instance details

Defined in Data.Map.Util

Methods

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

sequenceA :: Applicative f => Bias dir (f a) -> f (Bias dir a) #

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

sequence :: Monad m => Bias dir (m a) -> m (Bias dir a) #

Eq a => Eq (Bias dir a) Source # 
Instance details

Defined in Data.Map.Util

Methods

(==) :: Bias dir a -> Bias dir a -> Bool #

(/=) :: Bias dir a -> Bias dir a -> Bool #

(Typeable dir, Data a) => Data (Bias dir a) Source # 
Instance details

Defined in Data.Map.Util

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bias dir a -> c (Bias dir a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bias dir a) #

toConstr :: Bias dir a -> Constr #

dataTypeOf :: Bias dir a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Bias dir a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Bias dir a)) #

gmapT :: (forall b. Data b => b -> b) -> Bias dir a -> Bias dir a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bias dir a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bias dir a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bias dir a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bias dir a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bias dir a -> m (Bias dir a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bias dir a -> m (Bias dir a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bias dir a -> m (Bias dir a) #

Ord a => Ord (Bias dir a) Source # 
Instance details

Defined in Data.Map.Util

Methods

compare :: Bias dir a -> Bias dir a -> Ordering #

(<) :: Bias dir a -> Bias dir a -> Bool #

(<=) :: Bias dir a -> Bias dir a -> Bool #

(>) :: Bias dir a -> Bias dir a -> Bool #

(>=) :: Bias dir a -> Bias dir a -> Bool #

max :: Bias dir a -> Bias dir a -> Bias dir a #

min :: Bias dir a -> Bias dir a -> Bias dir a #

Read a => Read (Bias dir a) Source # 
Instance details

Defined in Data.Map.Util

Methods

readsPrec :: Int -> ReadS (Bias dir a) #

readList :: ReadS [Bias dir a] #

readPrec :: ReadPrec (Bias dir a) #

readListPrec :: ReadPrec [Bias dir a] #

Show a => Show (Bias dir a) Source # 
Instance details

Defined in Data.Map.Util

Methods

showsPrec :: Int -> Bias dir a -> ShowS #

show :: Bias dir a -> String #

showList :: [Bias dir a] -> ShowS #

(Ord k, Semigroup v) => Semigroup (Bias R (OMap k v)) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

(<>) :: Bias R (OMap k v) -> Bias R (OMap k v) -> Bias R (OMap k v) #

sconcat :: NonEmpty (Bias R (OMap k v)) -> Bias R (OMap k v) #

stimes :: Integral b => b -> Bias R (OMap k v) -> Bias R (OMap k v) #

Ord a => Semigroup (Bias R (OSet a)) Source # 
Instance details

Defined in Data.Set.Ordered

Methods

(<>) :: Bias R (OSet a) -> Bias R (OSet a) -> Bias R (OSet a) #

sconcat :: NonEmpty (Bias R (OSet a)) -> Bias R (OSet a) #

stimes :: Integral b => b -> Bias R (OSet a) -> Bias R (OSet a) #

(Ord k, Semigroup v) => Semigroup (Bias L (OMap k v)) Source # 
Instance details

Defined in Data.Map.Ordered.Internal

Methods

(<>) :: Bias L (OMap k v) -> Bias L (OMap k v) -> Bias L (OMap k v) #

sconcat :: NonEmpty (Bias L (OMap k v)) -> Bias L (OMap k v) #

stimes :: Integral b => b -> Bias L (OMap k v) -> Bias L (OMap k v) #

Ord a => Semigroup (Bias L (OSet a)) Source # 
Instance details

Defined in Data.Set.Ordered

Methods

(<>) :: Bias L (OSet a) -> Bias L (OSet a) -> Bias L (OSet a) #

sconcat :: NonEmpty (Bias L (OSet a)) -> Bias L (OSet a) #

stimes :: Integral b => b -> Bias L (OSet a) -> Bias L (OSet a) #

(Ord k, Monoid v) => Monoid (Bias R (OMap k v)) Source #

Empty maps and map union. When combining two sets that share elements, the indices of the right argument are preferred, and the values are combined with mappend.

See the asymptotics of unionWithR.

Instance details

Defined in Data.Map.Ordered.Internal

Methods

mempty :: Bias R (OMap k v) #

mappend :: Bias R (OMap k v) -> Bias R (OMap k v) -> Bias R (OMap k v) #

mconcat :: [Bias R (OMap k v)] -> Bias R (OMap k v) #

Ord a => Monoid (Bias R (OSet a)) Source #

Empty sets and set union. When combining two sets that share elements, the indices of the right argument are preferred.

See the asymptotics of (<>|).

Instance details

Defined in Data.Set.Ordered

Methods

mempty :: Bias R (OSet a) #

mappend :: Bias R (OSet a) -> Bias R (OSet a) -> Bias R (OSet a) #

mconcat :: [Bias R (OSet a)] -> Bias R (OSet a) #

(Ord k, Monoid v) => Monoid (Bias L (OMap k v)) Source #

Empty maps and map union. When combining two sets that share elements, the indices of the left argument are preferred, and the values are combined with mappend.

See the asymptotics of unionWithL.

Instance details

Defined in Data.Map.Ordered.Internal

Methods

mempty :: Bias L (OMap k v) #

mappend :: Bias L (OMap k v) -> Bias L (OMap k v) -> Bias L (OMap k v) #

mconcat :: [Bias L (OMap k v)] -> Bias L (OMap k v) #

Ord a => Monoid (Bias L (OSet a)) Source #

Empty sets and set union. When combining two sets that share elements, the indices of the left argument are preferred.

See the asymptotics of (|<>).

Instance details

Defined in Data.Set.Ordered

Methods

mempty :: Bias L (OSet a) #

mappend :: Bias L (OSet a) -> Bias L (OSet a) -> Bias L (OSet a) #

mconcat :: [Bias L (OSet a)] -> Bias L (OSet a) #

type L = L Source #

type R = R Source #

Deletion

delete :: Ord k => k -> OMap k v -> OMap k v Source #

filter :: Ord k => (k -> v -> Bool) -> OMap k v -> OMap k v Source #

filter f m contains exactly the key-value pairs of m that satisfy f, without changing the order they appear

(\\) :: Ord k => OMap k v -> OMap k v' -> OMap k v Source #

m \\ n deletes all the keys that exist in n from m

O(m*log(n)) where m is the size of the smaller map and n is the size of the larger map.

(|/\) :: Ord k => OMap k v -> OMap k v' -> OMap k v Source #

Intersection. (The /\ is intended to look a bit like the standard mathematical notation for set intersection.)

See asymptotics of intersectionWith.

(/\|) :: Ord k => OMap k v -> OMap k v' -> OMap k v Source #

Intersection. (The /\ is intended to look a bit like the standard mathematical notation for set intersection.)

See asymptotics of intersectionWith.

intersectionWith :: Ord k => (k -> v -> v' -> v'') -> OMap k v -> OMap k v' -> OMap k v'' Source #

Take the intersection. The first OMap 's argument's indices are used for the result.

O(m*log(n/(m+1)) + r*log(r)) where m is the size of the smaller map, n is the size of the larger map, and r is the size of the result.

Query

null :: OMap k v -> Bool Source #

size :: OMap k v -> Int Source #

member :: Ord k => k -> OMap k v -> Bool Source #

notMember :: Ord k => k -> OMap k v -> Bool Source #

lookup :: Ord k => k -> OMap k v -> Maybe v Source #

Indexing

type Index = Int Source #

A 0-based index, much like the indices used by lists' !! operation. All indices are with respect to insertion order.

findIndex :: Ord k => k -> OMap k v -> Maybe Index Source #

elemAt :: OMap k v -> Index -> Maybe (k, v) Source #

List conversions

fromList :: Ord k => [(k, v)] -> OMap k v Source #

If a key appears multiple times, the first occurrence is used for ordering and the last occurrence is used for its value. The library author welcomes comments on whether this default is sane.

assocs :: OMap k v -> [(k, v)] Source #

Return key-value pairs in the order they were inserted.

toAscList :: OMap k v -> [(k, v)] Source #

Return key-value pairs in order of increasing key.

Map conversion

toMap :: OMap k v -> Map k v Source #

Convert an OMap to a Map.

O(n), where n is the size of the OMap.