{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE TypeFamilies #-}
#endif
module Data.Bimap (
Bimap(),
null,
size,
member,
memberR,
notMember,
notMemberR,
pairMember,
pairNotMember,
lookup,
lookupR,
(!),
(!>),
(!?),
(!?>),
empty,
singleton,
insert,
tryInsert,
adjust,
adjustR,
adjustWithKey,
adjustWithKeyR,
update,
updateR,
updateWithKey,
updateWithKeyR,
delete,
deleteR,
findMin,
findMinR,
findMax,
findMaxR,
deleteMin,
deleteMinR,
deleteMax,
deleteMaxR,
deleteFindMin,
deleteFindMinR,
deleteFindMax,
deleteFindMaxR,
filter,
partition,
fromList,
fromAList,
fromAscPairList,
fromAscPairListUnchecked,
toList,
toAscList,
toAscListR,
keys,
keysR,
elems,
assocs,
fold,
Data.Bimap.map,
mapR,
mapMonotonic,
mapMonotonicR,
toMap,
toMapR,
valid,
twist,
twisted,
) where
import Control.DeepSeq (NFData)
import Control.Monad.Catch
import Data.Function (on)
import Data.List (foldl', sort)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Typeable
#if __GLASGOW_HASKELL__ >= 708
import qualified Data.BimapExt as GHCExts
#endif
import GHC.Generics (Generic)
import Prelude hiding (filter, lookup, null, pred)
import qualified Prelude as P
infixr 9 .:
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
.: :: forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
(.:) = forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
data Bimap a b = MkBimap !(M.Map a b) !(M.Map b a) deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b x. Rep (Bimap a b) x -> Bimap a b
forall a b x. Bimap a b -> Rep (Bimap a b) x
$cto :: forall a b x. Rep (Bimap a b) x -> Bimap a b
$cfrom :: forall a b x. Bimap a b -> Rep (Bimap a b) x
Generic)
instance (Show a, Show b) => Show (Bimap a b) where
show :: Bimap a b -> String
show Bimap a b
x = String
"fromList " forall a. [a] -> [a] -> [a]
++ (forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> [(a, b)]
toList forall a b. (a -> b) -> a -> b
$ Bimap a b
x)
instance (Eq a, Eq b) => Eq (Bimap a b) where
== :: Bimap a b -> Bimap a b -> Bool
(==) = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. Bimap a b -> [(a, b)]
toAscList
instance (Ord a, Ord b) => Ord (Bimap a b) where
compare :: Bimap a b -> Bimap a b -> Ordering
compare = forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. Bimap a b -> [(a, b)]
toAscList
instance (NFData a, NFData b) => NFData (Bimap a b)
#if __GLASGOW_HASKELL__ >= 708
instance (Ord a, Ord b) => GHCExts.IsList (Bimap a b) where
type Item (Bimap a b) = (a, b)
fromList :: [Item (Bimap a b)] -> Bimap a b
fromList = forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
fromList
toList :: Bimap a b -> [Item (Bimap a b)]
toList = forall a b. Bimap a b -> [(a, b)]
toList
#endif
data BimapException = KeyNotFound String
deriving(BimapException -> BimapException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BimapException -> BimapException -> Bool
$c/= :: BimapException -> BimapException -> Bool
== :: BimapException -> BimapException -> Bool
$c== :: BimapException -> BimapException -> Bool
Eq, Int -> BimapException -> ShowS
[BimapException] -> ShowS
BimapException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BimapException] -> ShowS
$cshowList :: [BimapException] -> ShowS
show :: BimapException -> String
$cshow :: BimapException -> String
showsPrec :: Int -> BimapException -> ShowS
$cshowsPrec :: Int -> BimapException -> ShowS
Show, Typeable)
instance Exception BimapException
empty :: Bimap a b
empty :: forall a b. Bimap a b
empty = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap forall k a. Map k a
M.empty forall k a. Map k a
M.empty
singleton :: a -> b -> Bimap a b
singleton :: forall a b. a -> b -> Bimap a b
singleton a
x b
y = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap (forall k a. k -> a -> Map k a
M.singleton a
x b
y) (forall k a. k -> a -> Map k a
M.singleton b
y a
x)
null :: Bimap a b -> Bool
null :: forall a b. Bimap a b -> Bool
null (MkBimap Map a b
left Map b a
_) = forall k a. Map k a -> Bool
M.null Map a b
left
size :: Bimap a b -> Int
size :: forall a b. Bimap a b -> Int
size (MkBimap Map a b
left Map b a
_) = forall k a. Map k a -> Int
M.size Map a b
left
member :: (Ord a, Ord b) => a -> Bimap a b -> Bool
member :: forall a b. (Ord a, Ord b) => a -> Bimap a b -> Bool
member a
x (MkBimap Map a b
left Map b a
_) = forall k a. Ord k => k -> Map k a -> Bool
M.member a
x Map a b
left
memberR :: (Ord a, Ord b) => b -> Bimap a b -> Bool
memberR :: forall a b. (Ord a, Ord b) => b -> Bimap a b -> Bool
memberR b
y (MkBimap Map a b
_ Map b a
right) = forall k a. Ord k => k -> Map k a -> Bool
M.member b
y Map b a
right
notMember :: (Ord a, Ord b) => a -> Bimap a b -> Bool
notMember :: forall a b. (Ord a, Ord b) => a -> Bimap a b -> Bool
notMember = Bool -> Bool
not forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: forall a b. (Ord a, Ord b) => a -> Bimap a b -> Bool
member
notMemberR :: (Ord a, Ord b) => b -> Bimap a b -> Bool
notMemberR :: forall a b. (Ord a, Ord b) => b -> Bimap a b -> Bool
notMemberR = Bool -> Bool
not forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: forall a b. (Ord a, Ord b) => b -> Bimap a b -> Bool
memberR
pairMember :: (Ord a, Ord b)
=> (a, b) -> Bimap a b -> Bool
pairMember :: forall a b. (Ord a, Ord b) => (a, b) -> Bimap a b -> Bool
pairMember (a
x, b
y) (MkBimap Map a b
left Map b a
_) =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (forall a. Eq a => a -> a -> Bool
== b
y) (forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup a
x Map a b
left)
pairNotMember :: (Ord a, Ord b)
=> (a, b) -> Bimap a b -> Bool
pairNotMember :: forall a b. (Ord a, Ord b) => (a, b) -> Bimap a b -> Bool
pairNotMember = Bool -> Bool
not forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: forall a b. (Ord a, Ord b) => (a, b) -> Bimap a b -> Bool
pairMember
insert :: (Ord a, Ord b)
=> a -> b -> Bimap a b -> Bimap a b
insert :: forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
insert a
x b
y = forall a b. (Ord a, Ord b) => a -> Bimap a b -> Bimap a b
delete a
x forall {a} {b} {c}. (a -> b) -> (b -> c) -> a -> c
>>> forall a b. (Ord a, Ord b) => b -> Bimap a b -> Bimap a b
deleteR b
y forall {a} {b} {c}. (a -> b) -> (b -> c) -> a -> c
>>> forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
unsafeInsert a
x b
y
where
>>> :: (a -> b) -> (b -> c) -> a -> c
(>>>) = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
tryInsert :: (Ord a, Ord b)
=> a -> b -> Bimap a b -> Bimap a b
tryInsert :: forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
tryInsert a
x b
y Bimap a b
bi
| a
x forall a b. (Ord a, Ord b) => a -> Bimap a b -> Bool
`notMember` Bimap a b
bi Bool -> Bool -> Bool
&& b
y forall a b. (Ord a, Ord b) => b -> Bimap a b -> Bool
`notMemberR` Bimap a b
bi = forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
unsafeInsert a
x b
y Bimap a b
bi
| Bool
otherwise = Bimap a b
bi
unsafeInsert :: (Ord a, Ord b)
=> a -> b -> Bimap a b -> Bimap a b
unsafeInsert :: forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
unsafeInsert a
x b
y (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert a
x b
y Map a b
left) (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert b
y a
x Map b a
right)
deleteE :: (Ord a, Ord b)
=> Either a b -> Bimap a b -> Bimap a b
deleteE :: forall a b. (Ord a, Ord b) => Either a b -> Bimap a b -> Bimap a b
deleteE Either a b
e (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap
(forall {a} {a}. (a -> a -> a) -> Maybe a -> a -> a
perhaps forall k a. Ord k => k -> Map k a -> Map k a
M.delete Maybe a
x Map a b
left)
(forall {a} {a}. (a -> a -> a) -> Maybe a -> a -> a
perhaps forall k a. Ord k => k -> Map k a -> Map k a
M.delete Maybe b
y Map b a
right)
where
perhaps :: (a -> a -> a) -> Maybe a -> a -> a
perhaps = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id
x :: Maybe a
x = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> Maybe a
Just (forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map b a
right) Either a b
e
y :: Maybe b
y = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map a b
left) forall a. a -> Maybe a
Just Either a b
e
delete :: (Ord a, Ord b) => a -> Bimap a b -> Bimap a b
delete :: forall a b. (Ord a, Ord b) => a -> Bimap a b -> Bimap a b
delete = forall a b. (Ord a, Ord b) => Either a b -> Bimap a b -> Bimap a b
deleteE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left
deleteR :: (Ord a, Ord b) => b -> Bimap a b -> Bimap a b
deleteR :: forall a b. (Ord a, Ord b) => b -> Bimap a b -> Bimap a b
deleteR = forall a b. (Ord a, Ord b) => Either a b -> Bimap a b -> Bimap a b
deleteE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right
adjust :: (Ord a, Ord b) => (b -> b) -> a -> Bimap a b -> Bimap a b
adjust :: forall a b.
(Ord a, Ord b) =>
(b -> b) -> a -> Bimap a b -> Bimap a b
adjust b -> b
f = forall a b.
(Ord a, Ord b) =>
(a -> b -> b) -> a -> Bimap a b -> Bimap a b
adjustWithKey (forall a b. a -> b -> a
const b -> b
f)
adjustR :: (Ord a, Ord b) => (a -> a) -> b -> Bimap a b -> Bimap a b
adjustR :: forall a b.
(Ord a, Ord b) =>
(a -> a) -> b -> Bimap a b -> Bimap a b
adjustR a -> a
f b
b = forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b.
(Ord a, Ord b) =>
(b -> b) -> a -> Bimap a b -> Bimap a b
adjust a -> a
f b
b forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap
where reverseBimap :: Bimap b a -> Bimap a b
reverseBimap (MkBimap Map b a
left Map a b
right) = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
right Map b a
left
adjustWithKey :: (Ord a, Ord b) => (a -> b -> b) -> a -> Bimap a b -> Bimap a b
adjustWithKey :: forall a b.
(Ord a, Ord b) =>
(a -> b -> b) -> a -> Bimap a b -> Bimap a b
adjustWithKey a -> b -> b
f = forall a b.
(Ord a, Ord b) =>
(a -> b -> Maybe b) -> a -> Bimap a b -> Bimap a b
updateWithKey (\a
a -> forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b -> b
f a
a)
adjustWithKeyR :: (Ord a, Ord b) => (b -> a -> a) -> b -> Bimap a b -> Bimap a b
adjustWithKeyR :: forall a b.
(Ord a, Ord b) =>
(b -> a -> a) -> b -> Bimap a b -> Bimap a b
adjustWithKeyR b -> a -> a
f b
b = forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b.
(Ord a, Ord b) =>
(a -> b -> b) -> a -> Bimap a b -> Bimap a b
adjustWithKey b -> a -> a
f b
b forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap
where reverseBimap :: Bimap b a -> Bimap a b
reverseBimap (MkBimap Map b a
left Map a b
right) = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
right Map b a
left
update :: (Ord a, Ord b) => (b -> Maybe b) -> a -> Bimap a b -> Bimap a b
update :: forall a b.
(Ord a, Ord b) =>
(b -> Maybe b) -> a -> Bimap a b -> Bimap a b
update b -> Maybe b
f = forall a b.
(Ord a, Ord b) =>
(a -> b -> Maybe b) -> a -> Bimap a b -> Bimap a b
updateWithKey (forall a b. a -> b -> a
const b -> Maybe b
f)
updateR :: (Ord a, Ord b) => (a -> Maybe a) -> b -> Bimap a b -> Bimap a b
updateR :: forall a b.
(Ord a, Ord b) =>
(a -> Maybe a) -> b -> Bimap a b -> Bimap a b
updateR a -> Maybe a
f b
b = forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b.
(Ord a, Ord b) =>
(b -> Maybe b) -> a -> Bimap a b -> Bimap a b
update a -> Maybe a
f b
b forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap
where reverseBimap :: Bimap b a -> Bimap a b
reverseBimap (MkBimap Map b a
left Map a b
right) = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
right Map b a
left
updateWithKey :: (Ord a, Ord b) => (a -> b -> Maybe b) -> a -> Bimap a b -> Bimap a b
updateWithKey :: forall a b.
(Ord a, Ord b) =>
(a -> b -> Maybe b) -> a -> Bimap a b -> Bimap a b
updateWithKey a -> b -> Maybe b
f a
a (MkBimap Map a b
left Map b a
right) = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
left' Map b a
right' where
oldB :: Maybe b
oldB = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup a
a Map a b
left
newB :: Maybe b
newB = a -> b -> Maybe b
f a
a forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe b
oldB
oldA :: Maybe a
oldA = Maybe b
newB forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map b a
right) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
x -> if a
x forall a. Eq a => a -> a -> Bool
== a
a then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just a
x
left' :: Map a b
left' = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall k a. Ord k => k -> Map k a -> Map k a
M.delete Maybe a
oldA forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
M.updateWithKey a -> b -> Maybe b
f a
a Map a b
left
right' :: Map b a
right' = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (forall k a. Ord k => k -> a -> Map k a -> Map k a
`M.insert` a
a) Maybe b
newB forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall k a. Ord k => k -> Map k a -> Map k a
M.delete Maybe b
oldB Map b a
right
updateWithKeyR :: (Ord a, Ord b) => (b -> a -> Maybe a) -> b -> Bimap a b -> Bimap a b
updateWithKeyR :: forall a b.
(Ord a, Ord b) =>
(b -> a -> Maybe a) -> b -> Bimap a b -> Bimap a b
updateWithKeyR b -> a -> Maybe a
f b
b = forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b.
(Ord a, Ord b) =>
(a -> b -> Maybe b) -> a -> Bimap a b -> Bimap a b
updateWithKey b -> a -> Maybe a
f b
b forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
reverseBimap
where reverseBimap :: Bimap b a -> Bimap a b
reverseBimap (MkBimap Map b a
left Map a b
right) = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
right Map b a
left
lookup :: (Ord a, Ord b, MonadThrow m)
=> a -> Bimap a b -> m b
lookup :: forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
a -> Bimap a b -> m b
lookup a
x (MkBimap Map a b
left Map b a
_) =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM forall a b. (a -> b) -> a -> b
$ String -> BimapException
KeyNotFound String
"Data.Bimap.lookup")
forall (m :: * -> *) a. Monad m => a -> m a
return
(forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup a
x Map a b
left)
lookupR :: (Ord a, Ord b, MonadThrow m)
=> b -> Bimap a b -> m a
lookupR :: forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
b -> Bimap a b -> m a
lookupR b
y (MkBimap Map a b
_ Map b a
right) =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM forall a b. (a -> b) -> a -> b
$ String -> BimapException
KeyNotFound String
"Data.Bimap.lookupR")
forall (m :: * -> *) a. Monad m => a -> m a
return
(forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup b
y Map b a
right)
(!) :: (Ord a, Ord b) => Bimap a b -> a -> b
! :: forall a b. (Ord a, Ord b) => Bimap a b -> a -> b
(!) Bimap a b
bi a
x = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"Data.Bimap.(!): Left key not found") forall a b. (a -> b) -> a -> b
$ forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
a -> Bimap a b -> m b
lookup a
x Bimap a b
bi
(!>) :: (Ord a, Ord b) => Bimap a b -> b -> a
!> :: forall a b. (Ord a, Ord b) => Bimap a b -> b -> a
(!>) Bimap a b
bi b
y = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"Data.Bimap.(!>): Right key not found") forall a b. (a -> b) -> a -> b
$ forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
b -> Bimap a b -> m a
lookupR b
y Bimap a b
bi
(!?) :: (Ord a, Ord b, MonadThrow m) => Bimap a b -> a -> m b
!? :: forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
Bimap a b -> a -> m b
(!?) = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
a -> Bimap a b -> m b
lookup
(!?>) :: (Ord a, Ord b, MonadThrow m) => Bimap a b -> b -> m a
!?> :: forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
Bimap a b -> b -> m a
(!?>) = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b (m :: * -> *).
(Ord a, Ord b, MonadThrow m) =>
b -> Bimap a b -> m a
lookupR
fromList :: (Ord a, Ord b)
=> [(a, b)] -> Bimap a b
fromList :: forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
fromList = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. (a -> b) -> a -> b
$ forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
insert) forall a b. Bimap a b
empty
fromAList :: (Ord a, Ord b)
=> [(a, b)] -> Bimap a b
fromAList :: forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
fromAList = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. (a -> b) -> a -> b
$ forall a b. (Ord a, Ord b) => a -> b -> Bimap a b -> Bimap a b
tryInsert) forall a b. Bimap a b
empty
toList :: Bimap a b -> [(a, b)]
toList :: forall a b. Bimap a b -> [(a, b)]
toList = forall a b. Bimap a b -> [(a, b)]
toAscList
fromAscPairList :: (Ord a, Ord b)
=> [(a, b)] -> Bimap a b
fromAscPairList :: forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
fromAscPairList [(a, b)]
xs
| forall a b. (Ord a, Ord b) => [(a, b)] -> Bool
isBiAscending [(a, b)]
xs = forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
fromAscPairListUnchecked [(a, b)]
xs
| Bool
otherwise = forall a. HasCallStack => String -> a
error
String
"Data.Bimap.fromAscPairList: list not correctly ascending"
isBiAscending :: (Ord a, Ord b)
=> [(a, b)] -> Bool
isBiAscending :: forall a b. (Ord a, Ord b) => [(a, b)] -> Bool
isBiAscending = forall c. (c -> c -> Bool) -> [c] -> Bool
allAdjacent forall {a} {a}. (Ord a, Ord a) => (a, a) -> (a, a) -> Bool
bothLess
where
allAdjacent :: (c -> c -> Bool) -> [c] -> Bool
allAdjacent :: forall c. (c -> c -> Bool) -> [c] -> Bool
allAdjacent c -> c -> Bool
f [c]
xs = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry c -> c -> Bool
f) forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [c]
xs (forall a. [a] -> [a]
tail [c]
xs)
bothLess :: (a, a) -> (a, a) -> Bool
bothLess (a
x1, a
y1) (a
x2, a
y2) = (a
x1 forall a. Ord a => a -> a -> Bool
< a
x2) Bool -> Bool -> Bool
&& (a
y1 forall a. Ord a => a -> a -> Bool
< a
y2)
fromAscPairListUnchecked :: (Ord a, Ord b)
=> [(a, b)] -> Bimap a b
fromAscPairListUnchecked :: forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
fromAscPairListUnchecked [(a, b)]
xs = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap
(forall k a. Eq k => [(k, a)] -> Map k a
M.fromAscList [(a, b)]
xs)
(forall k a. Eq k => [(k, a)] -> Map k a
M.fromAscList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
P.map forall {b} {a}. (b, a) -> (a, b)
swap [(a, b)]
xs)
where
swap :: (b, a) -> (a, b)
swap (b
x, a
y) = (a
y, b
x)
toAscList :: Bimap a b -> [(a, b)]
toAscList :: forall a b. Bimap a b -> [(a, b)]
toAscList (MkBimap Map a b
left Map b a
_) = forall k a. Map k a -> [(k, a)]
M.toList Map a b
left
toAscListR :: Bimap a b -> [(b, a)]
toAscListR :: forall a b. Bimap a b -> [(b, a)]
toAscListR = forall a b. Bimap a b -> [(a, b)]
toAscList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
twist
assocs :: Bimap a b -> [(a, b)]
assocs :: forall a b. Bimap a b -> [(a, b)]
assocs = forall a b. Bimap a b -> [(a, b)]
toList
keys :: Bimap a b -> [a]
keys :: forall a b. Bimap a b -> [a]
keys (MkBimap Map a b
left Map b a
_) = forall k a. Map k a -> [k]
M.keys Map a b
left
keysR :: Bimap a b -> [b]
keysR :: forall a b. Bimap a b -> [b]
keysR (MkBimap Map a b
_ Map b a
right) = forall k a. Map k a -> [k]
M.keys Map b a
right
elems :: Bimap a b -> [b]
elems :: forall a b. Bimap a b -> [b]
elems = forall a b. Bimap a b -> [b]
keysR
toMap :: Bimap a b -> M.Map a b
toMap :: forall a b. Bimap a b -> Map a b
toMap (MkBimap Map a b
left Map b a
_) = Map a b
left
toMapR :: Bimap a b -> M.Map b a
toMapR :: forall a b. Bimap a b -> Map b a
toMapR (MkBimap Map a b
_ Map b a
right) = Map b a
right
filter :: (Ord a, Ord b)
=> (a -> b -> Bool) -> Bimap a b -> Bimap a b
filter :: forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> Bimap a b
filter a -> b -> Bool
pred (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap
(forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey a -> b -> Bool
pred Map a b
left)
(forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey (forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> Bool
pred) Map b a
right)
partition :: (Ord a, Ord b)
=> (a -> b -> Bool) -> Bimap a b -> (Bimap a b, Bimap a b)
partition :: forall a b.
(Ord a, Ord b) =>
(a -> b -> Bool) -> Bimap a b -> (Bimap a b, Bimap a b)
partition a -> b -> Bool
pred (MkBimap Map a b
left Map b a
right) =
(,) (forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
leftA Map b a
rightA) (forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
leftB Map b a
rightB)
where
(Map a b
leftA, Map a b
leftB) = forall k a. (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
M.partitionWithKey a -> b -> Bool
pred Map a b
left
(Map b a
rightA, Map b a
rightB) = forall k a. (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
M.partitionWithKey (forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> Bool
pred) Map b a
right
valid :: (Ord a, Ord b)
=> Bimap a b -> Bool
valid :: forall a b. (Ord a, Ord b) => Bimap a b -> Bool
valid (MkBimap Map a b
left Map b a
right) = forall (t :: * -> *). Foldable t => t Bool -> Bool
and
[ forall k a. Ord k => Map k a -> Bool
M.valid Map a b
left, forall k a. Ord k => Map k a -> Bool
M.valid Map b a
right
, forall a. Eq a => a -> a -> Bool
(==)
(forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
M.toList forall a b. (a -> b) -> a -> b
$ Map a b
left )
(forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
P.map forall {b} {a}. (b, a) -> (a, b)
flipPair forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
M.toList forall a b. (a -> b) -> a -> b
$ Map b a
right)
]
where
flipPair :: (b, a) -> (a, b)
flipPair (b
x, a
y) = (a
y, b
x)
twist :: Bimap a b -> Bimap b a
twist :: forall {b} {a}. Bimap b a -> Bimap a b
twist (MkBimap Map a b
left Map b a
right) = forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map b a
right Map a b
left
twisted :: (Bimap a b -> Bimap a b) -> (Bimap b a -> Bimap b a)
twisted :: forall a b. (Bimap a b -> Bimap a b) -> Bimap b a -> Bimap b a
twisted Bimap a b -> Bimap a b
f = forall {b} {a}. Bimap b a -> Bimap a b
twist forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bimap a b -> Bimap a b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
twist
fold :: (a -> b -> c -> c) -> c -> Bimap a b -> c
fold :: forall a b c. (a -> b -> c -> c) -> c -> Bimap a b -> c
fold a -> b -> c -> c
f c
z = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> b -> c -> c
f) c
z forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> [(a, b)]
assocs
map :: Ord c => (a -> c) -> Bimap a b -> Bimap c b
map :: forall c a b. Ord c => (a -> c) -> Bimap a b -> Bimap c b
map a -> c
f (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap (forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeys a -> c
f Map a b
left) (forall a b k. (a -> b) -> Map k a -> Map k b
M.map a -> c
f Map b a
right)
mapR :: Ord c => (b -> c) -> Bimap a b -> Bimap a c
mapR :: forall c b a. Ord c => (b -> c) -> Bimap a b -> Bimap a c
mapR b -> c
f (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap (forall a b k. (a -> b) -> Map k a -> Map k b
M.map b -> c
f Map a b
left) (forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeys b -> c
f Map b a
right)
mapMonotonic :: (a -> c) -> Bimap a b -> Bimap c b
mapMonotonic :: forall a c b. (a -> c) -> Bimap a b -> Bimap c b
mapMonotonic a -> c
f (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap (forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeysMonotonic a -> c
f Map a b
left) (forall a b k. (a -> b) -> Map k a -> Map k b
M.map a -> c
f Map b a
right)
mapMonotonicR :: (b -> c) -> Bimap a b -> Bimap a c
mapMonotonicR :: forall b c a. (b -> c) -> Bimap a b -> Bimap a c
mapMonotonicR b -> c
f (MkBimap Map a b
left Map b a
right) =
forall a b. Map a b -> Map b a -> Bimap a b
MkBimap (forall a b k. (a -> b) -> Map k a -> Map k b
M.map b -> c
f Map a b
left) (forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeysMonotonic b -> c
f Map b a
right)
deleteFindMax :: (Ord b) => Bimap a b -> ((a, b), Bimap a b)
deleteFindMax :: forall b a. Ord b => Bimap a b -> ((a, b), Bimap a b)
deleteFindMax (MkBimap Map a b
left Map b a
right) = ((a
a, b
b), forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
left' Map b a
right') where
((a
a, b
b), Map a b
left') = forall k a. Map k a -> ((k, a), Map k a)
M.deleteFindMax Map a b
left
right' :: Map b a
right' = b
b forall k a. Ord k => k -> Map k a -> Map k a
`M.delete` Map b a
right
deleteFindMaxR :: (Ord a) => Bimap a b -> ((b, a), Bimap a b)
deleteFindMaxR :: forall a b. Ord a => Bimap a b -> ((b, a), Bimap a b)
deleteFindMaxR = forall {t} {b} {a}. (t -> b) -> (a, t) -> (a, b)
second forall {b} {a}. Bimap b a -> Bimap a b
twist forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => Bimap a b -> ((a, b), Bimap a b)
deleteFindMax forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
twist where
second :: (t -> b) -> (a, t) -> (a, b)
second t -> b
f (a
x, t
y) = (a
x, t -> b
f t
y)
deleteMax :: (Ord b) => Bimap a b -> Bimap a b
deleteMax :: forall b a. Ord b => Bimap a b -> Bimap a b
deleteMax = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => Bimap a b -> ((a, b), Bimap a b)
deleteFindMax
deleteMaxR :: (Ord a) => Bimap a b -> Bimap a b
deleteMaxR :: forall a b. Ord a => Bimap a b -> Bimap a b
deleteMaxR = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Ord a => Bimap a b -> ((b, a), Bimap a b)
deleteFindMaxR
findMax :: Bimap a b -> (a, b)
findMax :: forall a b. Bimap a b -> (a, b)
findMax = forall k a. Map k a -> (k, a)
M.findMax forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> Map a b
toMap
findMaxR :: Bimap a b -> (b, a)
findMaxR :: forall a b. Bimap a b -> (b, a)
findMaxR = forall k a. Map k a -> (k, a)
M.findMax forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> Map b a
toMapR
deleteFindMin :: (Ord b) => Bimap a b -> ((a, b), Bimap a b)
deleteFindMin :: forall b a. Ord b => Bimap a b -> ((a, b), Bimap a b)
deleteFindMin (MkBimap Map a b
left Map b a
right) = ((a
a, b
b), forall a b. Map a b -> Map b a -> Bimap a b
MkBimap Map a b
left' Map b a
right') where
((a
a, b
b), Map a b
left') = forall k a. Map k a -> ((k, a), Map k a)
M.deleteFindMin Map a b
left
right' :: Map b a
right' = b
b forall k a. Ord k => k -> Map k a -> Map k a
`M.delete` Map b a
right
deleteFindMinR :: (Ord a) => Bimap a b -> ((b, a), Bimap a b)
deleteFindMinR :: forall a b. Ord a => Bimap a b -> ((b, a), Bimap a b)
deleteFindMinR = forall {t} {b} {a}. (t -> b) -> (a, t) -> (a, b)
second forall {b} {a}. Bimap b a -> Bimap a b
twist forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => Bimap a b -> ((a, b), Bimap a b)
deleteFindMin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b} {a}. Bimap b a -> Bimap a b
twist where
second :: (t -> b) -> (a, t) -> (a, b)
second t -> b
f (a
x, t
y) = (a
x, t -> b
f t
y)
deleteMin :: (Ord b) => Bimap a b -> Bimap a b
deleteMin :: forall b a. Ord b => Bimap a b -> Bimap a b
deleteMin = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => Bimap a b -> ((a, b), Bimap a b)
deleteFindMin
deleteMinR :: (Ord a) => Bimap a b -> Bimap a b
deleteMinR :: forall a b. Ord a => Bimap a b -> Bimap a b
deleteMinR = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Ord a => Bimap a b -> ((b, a), Bimap a b)
deleteFindMinR
findMin :: Bimap a b -> (a, b)
findMin :: forall a b. Bimap a b -> (a, b)
findMin = forall k a. Map k a -> (k, a)
M.findMin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> Map a b
toMap
findMinR :: Bimap a b -> (b, a)
findMinR :: forall a b. Bimap a b -> (b, a)
findMinR = forall k a. Map k a -> (k, a)
M.findMin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Bimap a b -> Map b a
toMapR