bimap-0.4.0: Bidirectional mapping between two key types

Safe HaskellNone
LanguageHaskell98

Data.Bimap

Contents

Description

An implementation of bidirectional maps between values of two key types. A Bimap is essentially a bijection between subsets of its two argument types.

Each element of the left-hand type is associated with an element of the right-hand type, and vice-versa, such that the two mappings are inverses. Deleting an element will cause its twin to be deleted, and inserting a pair of elements will cause any overlapping bindings to be deleted.

Most functions implicitly consider the left-hand type to be the key, and the right-hand type to be the value. Functions with an R suffix reverse this convention, treating the right-hand type as the key and the left-hand type as the value.

Synopsis

Bimap type

data Bimap a b Source #

A bidirectional map between values of types a and b.

Instances
(Ord a, Ord b) => IsList (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

Associated Types

type Item (Bimap a b) :: Type #

Methods

fromList :: [Item (Bimap a b)] -> Bimap a b #

fromListN :: Int -> [Item (Bimap a b)] -> Bimap a b #

toList :: Bimap a b -> [Item (Bimap a b)] #

(Eq a, Eq b) => Eq (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

Methods

(==) :: Bimap a b -> Bimap a b -> Bool #

(/=) :: Bimap a b -> Bimap a b -> Bool #

(Ord a, Ord b) => Ord (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

Methods

compare :: Bimap a b -> Bimap a b -> Ordering #

(<) :: Bimap a b -> Bimap a b -> Bool #

(<=) :: Bimap a b -> Bimap a b -> Bool #

(>) :: Bimap a b -> Bimap a b -> Bool #

(>=) :: Bimap a b -> Bimap a b -> Bool #

max :: Bimap a b -> Bimap a b -> Bimap a b #

min :: Bimap a b -> Bimap a b -> Bimap a b #

(Show a, Show b) => Show (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

Methods

showsPrec :: Int -> Bimap a b -> ShowS #

show :: Bimap a b -> String #

showList :: [Bimap a b] -> ShowS #

Generic (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

Associated Types

type Rep (Bimap a b) :: Type -> Type #

Methods

from :: Bimap a b -> Rep (Bimap a b) x #

to :: Rep (Bimap a b) x -> Bimap a b #

(NFData a, NFData b) => NFData (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

Methods

rnf :: Bimap a b -> () #

type Rep (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

type Rep (Bimap a b) = D1 (MetaData "Bimap" "Data.Bimap" "bimap-0.4.0-4sTD2RtkouNAhFc8s7nibX" False) (C1 (MetaCons "MkBimap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map a b)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map b a))))
type Item (Bimap a b) Source # 
Instance details

Defined in Data.Bimap

type Item (Bimap a b) = (a, b)

Query

null :: Bimap a b -> Bool Source #

O(1). Is the bimap empty? Version: 0.2

size :: Bimap a b -> Int Source #

O(1). The number of elements in the bimap. Version: 0.2

member :: (Ord a, Ord b) => a -> Bimap a b -> Bool Source #

O(log n). Is the specified value a member of the bimap? Version: 0.2

memberR :: (Ord a, Ord b) => b -> Bimap a b -> Bool Source #

O(log n). A version of member specialized to the right key. Version: 0.2

notMember :: (Ord a, Ord b) => a -> Bimap a b -> Bool Source #

O(log n). Is the specified value not a member of the bimap? Version: 0.2

notMemberR :: (Ord a, Ord b) => b -> Bimap a b -> Bool Source #

O(log n). A version of notMember specialized to the right key. Version: 0.2

pairMember :: (Ord a, Ord b) => (a, b) -> Bimap a b -> Bool Source #

O(log n). Are the two values associated with each other in the bimap?

This function is uncurried in its first two arguments, so that it can be used infix.

Version: 0.2

pairNotMember :: (Ord a, Ord b) => (a, b) -> Bimap a b -> Bool Source #

O(log n). Are the two values not in the bimap, or not associated with each other? (Complement of pairMember.) Version: 0.2

lookup :: (Ord a, Ord b, MonadThrow m) => a -> Bimap a b -> m b Source #

O(log n). Lookup a left key in the bimap, returning the associated right key.

This function will return the result in the monad, or fail if the value isn't in the bimap.

Version: 0.2

lookupR :: (Ord a, Ord b, MonadThrow m) => b -> Bimap a b -> m a Source #

O(log n). A version of lookup that is specialized to the right key, and returns the corresponding left key. Version: 0.2

(!) :: (Ord a, Ord b) => Bimap a b -> a -> b Source #

O(log n). Find the right key corresponding to a given left key. Calls error when the key is not in the bimap. Version: 0.2

(!>) :: (Ord a, Ord b) => Bimap a b -> b -> a Source #

O(log n). A version of (!) that is specialized to the right key, and returns the corresponding left key. Version: 0.2

Construction

empty :: Bimap a b Source #

O(1). The empty bimap. Version: 0.2

singleton :: a -> b -> Bimap a b Source #

O(1). A bimap with a single element. Version: 0.2

Update

insert :: (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b Source #

O(log n). Insert a pair of values into the bimap, associating them.

If either of the values is already in the bimap, any overlapping bindings are deleted.

Version: 0.2

tryInsert :: (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b Source #

O(log n). Insert a pair of values into the bimap, but only if neither is already in the bimap. Version: 0.2.2

adjust :: (Ord a, Ord b) => (b -> b) -> a -> Bimap a b -> Bimap a b Source #

O(log n). Update a value at a specific left key with the result of the provided function.

When the left key is not a member of the bimap, the original bimap is returned.

adjustR :: (Ord a, Ord b) => (a -> a) -> b -> Bimap a b -> Bimap a b Source #

O(log n). Update a value at a specific right key with the result of the provided function.

When the right key is not a member of the bimap, the original bimap is returned.

adjustWithKey :: (Ord a, Ord b) => (a -> b -> b) -> a -> Bimap a b -> Bimap a b Source #

O(log n). Adjust a value at a specific left key.

When the left key is not a member of the bimap, the original bimap is returned.

adjustWithKeyR :: (Ord a, Ord b) => (b -> a -> a) -> b -> Bimap a b -> Bimap a b Source #

O(log n). Adjust a value at a specific right key.

When the right key is not a member of the bimap, the original bimap is returned.

update :: (Ord a, Ord b) => (b -> Maybe b) -> a -> Bimap a b -> Bimap a b Source #

O(log n). The expression (update f a bimap) updates the right value b at a (if it is in the bimap).

If (f b) is Nothing, the element is deleted.

If it is (Just y), the left key a is bound to the new value y.

updateR :: (Ord a, Ord b) => (a -> Maybe a) -> b -> Bimap a b -> Bimap a b Source #

O(log n). The expression (updateR f b bimap) updates the left value a at b (if it is in the bimap).

If (f a) is Nothing, the element is deleted.

If it is (Just x), the right key b is bound to the new value x.

updateWithKey :: (Ord a, Ord b) => (a -> b -> Maybe b) -> a -> Bimap a b -> Bimap a b Source #

O(log n). The expression (updateWithKey f a bimap) updates the right value b at a (if it is in the bimap).

If (f a b) is Nothing, the element is deleted.

If it is (Just y), the left key a is bound to the new value y.

updateWithKeyR :: (Ord a, Ord b) => (b -> a -> Maybe a) -> b -> Bimap a b -> Bimap a b Source #

O(log n). The expression (updateWithKeyR f b bimap) updates the left value a at b (if it is in the bimap).

If (f b a) is Nothing, the element is deleted.

If it is (Just x), the right key b is bound to the new value x.

delete :: (Ord a, Ord b) => a -> Bimap a b -> Bimap a b Source #

O(log n). Delete a value and its twin from a bimap.

When the value is not a member of the bimap, the original bimap is returned.

Version: 0.2

deleteR :: (Ord a, Ord b) => b -> Bimap a b -> Bimap a b Source #

O(log n) A version of delete specialized to the right key. Version: 0.2

Min/Max

findMin :: Bimap a b -> (a, b) Source #

O(log n). Find the element with minimal left key. Calls error if the bimap is empty. Version: 0.2.2

findMinR :: Bimap a b -> (b, a) Source #

O(log n). Find the element with minimal right key. The right-hand key is the first entry in the pair. Calls error if the bimap is empty. Version: 0.2.2

findMax :: Bimap a b -> (a, b) Source #

O(log n). Find the element with maximal left key. Calls error if the bimap is empty. Version: 0.2.2

findMaxR :: Bimap a b -> (b, a) Source #

O(log n). Find the element with maximal right key. The right-hand key is the first entry in the pair. Calls error if the bimap is empty. Version: 0.2.2

deleteMin :: Ord b => Bimap a b -> Bimap a b Source #

O(log n). Delete the element with minimal left key. Calls error if the bimap is empty. Version: 0.2.2

deleteMinR :: Ord a => Bimap a b -> Bimap a b Source #

O(log n). Delete the element with minimal right key. Calls error if the bimap is empty. Version: 0.2.2

deleteMax :: Ord b => Bimap a b -> Bimap a b Source #

O(log n). Delete the element with maximal left key. Calls error if the bimap is empty. Version: 0.2.2

deleteMaxR :: Ord a => Bimap a b -> Bimap a b Source #

O(log n). Delete the element with maximal right key. Calls error if the bimap is empty. Version: 0.2.2

deleteFindMin :: Ord b => Bimap a b -> ((a, b), Bimap a b) Source #

O(log n). Delete and find the element with minimal left key. Calls error if the bimap is empty. Version: 0.2.2

deleteFindMinR :: Ord a => Bimap a b -> ((b, a), Bimap a b) Source #

O(log n). Delete and find the element with minimal right key. Calls error if the bimap is empty. Version: 0.2.2

deleteFindMax :: Ord b => Bimap a b -> ((a, b), Bimap a b) Source #

O(log n). Delete and find the element with maximal left key. Calls error if the bimap is empty. Version: 0.2.2

deleteFindMaxR :: Ord a => Bimap a b -> ((b, a), Bimap a b) Source #

O(log n). Delete and find the element with maximal right key. Calls error if the bimap is empty. Version: 0.2.2

Filter

filter :: (Ord a, Ord b) => (a -> b -> Bool) -> Bimap a b -> Bimap a b Source #

O(n). Filter all association pairs that satisfy the predicate.

Note that the predicate will be applied twice for each association in the bimap.

Version: 0.2.4

partition :: (Ord a, Ord b) => (a -> b -> Bool) -> Bimap a b -> (Bimap a b, Bimap a b) Source #

O(n). Partition the bimap according to a predicate. The first bimap contains all associations that satisfy the predicate; the second contains all associations that fail the predicate.

Note that the predicate will be applied twice for each association in the bimap.

Version: 0.2.4

Conversion/traversal

fromList :: (Ord a, Ord b) => [(a, b)] -> Bimap a b Source #

O(n*log n). Build a map from a list of pairs. If there are any overlapping pairs in the list, the later ones will override the earlier ones. Version: 0.2

fromAList :: (Ord a, Ord b) => [(a, b)] -> Bimap a b Source #

O(n*log n). Build a map from a list of pairs. Unlike fromList, earlier pairs will take precedence over later ones.

The name fromAList is a reference to Lisp-style association lists, where associations can be overridden by prepending new ones.

Note that when duplicates occur in both the keys and in the values, fromList xs /= fromAList (reverse xs). However, if either contains no duplicates, then the equality holds.

Version: 0.2.2

fromAscPairList :: (Ord a, Ord b) => [(a, b)] -> Bimap a b Source #

O(n). Build a bimap from a list of pairs, where both the fst and snd halves of the list are in strictly ascending order.

This precondition is checked; an invalid list will cause an error.

Version: 0.2.3

fromAscPairListUnchecked :: (Ord a, Ord b) => [(a, b)] -> Bimap a b Source #

O(n). Build a bimap from a list of pairs, where both the fst and snd halves of the list are in strictly ascending order.

This precondition is not checked; an invalid list will produce a malformed bimap.

Version: 0.2.3

toList :: Bimap a b -> [(a, b)] Source #

O(n). Convert to a list of associated pairs. Version: 0.2

toAscList :: Bimap a b -> [(a, b)] Source #

O(n). Convert to a list of associated pairs, with the left-hand values in ascending order.

Since pair ordering is lexical, the pairs will also be in ascending order.

Version: 0.2

toAscListR :: Bimap a b -> [(b, a)] Source #

O(n). Convert to a list of associated pairs, with the right-hand values first in the pair and in ascending order.

Since pair ordering is lexical, the pairs will also be in ascending order.

Version: 0.2

keys :: Bimap a b -> [a] Source #

O(n). Return all left-hand keys in the bimap in ascending order. Version: 0.2

keysR :: Bimap a b -> [b] Source #

O(n). Return all right-hand keys in the bimap in ascending order. Version: 0.2

elems :: Bimap a b -> [b] Source #

O(n). An alias for keysR. Version: 0.2

assocs :: Bimap a b -> [(a, b)] Source #

O(n). Return all associated pairs in the bimap, with the left-hand values in ascending order. Version: 0.2

fold :: (a -> b -> c -> c) -> c -> Bimap a b -> c Source #

O(n). Fold the association pairs in the map, such that fold f z == foldr f z . assocs. Version: 0.2

map :: Ord c => (a -> c) -> Bimap a b -> Bimap c b Source #

O(n*log n) Map a function over all the left keys in the map. Version 0.3

mapR :: Ord c => (b -> c) -> Bimap a b -> Bimap a c Source #

O(n*log n) Map a function over all the right keys in the map. Version 0.3

mapMonotonic :: (a -> c) -> Bimap a b -> Bimap c b Source #

O(n). Map a strictly increasing function over all left keys in the map. The precondition is not checked. Version 0.3

mapMonotonicR :: (b -> c) -> Bimap a b -> Bimap a c Source #

O(n). Map a strictly increasing function over all right keys in the map. The precondition is not checked. Version 0.3

toMap :: Bimap a b -> Map a b Source #

O(1). Extract only the left-to-right component of a bimap. Version: 0.2.1

toMapR :: Bimap a b -> Map b a Source #

O(1). Extract only the right-to-left component of a bimap. Version: 0.2.1

Miscellaneous

valid :: (Ord a, Ord b) => Bimap a b -> Bool Source #

O(n*log n). Test if the internal bimap structure is valid. This should be true for any bimap created using the public interface, unless fromAscPairListUnchecked has been used inappropriately. Version: 0.2

twist :: Bimap a b -> Bimap b a Source #

O(1). Reverse the positions of the two element types in the bimap. Version: 0.2

twisted :: (Bimap a b -> Bimap a b) -> Bimap b a -> Bimap b a Source #

O(1). Reverse the positions of the two element types in a bimap transformation. Version: 0.2