bimap-many-0.1.0.0: Bidirectional many-to-many mapping between two key types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.BimapMany

Synopsis

BimapMany type

data BimapMany a b c Source #

Instances

Instances details
Functor (BimapMany a b) Source # 
Instance details

Defined in Data.BimapMany

Methods

fmap :: (a0 -> b0) -> BimapMany a b a0 -> BimapMany a b b0 #

(<$) :: a0 -> BimapMany a b b0 -> BimapMany a b a0 #

Foldable (BimapMany a b) Source # 
Instance details

Defined in Data.BimapMany

Methods

fold :: Monoid m => BimapMany a b m -> m #

foldMap :: Monoid m => (a0 -> m) -> BimapMany a b a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> BimapMany a b a0 -> m #

foldr :: (a0 -> b0 -> b0) -> b0 -> BimapMany a b a0 -> b0 #

foldr' :: (a0 -> b0 -> b0) -> b0 -> BimapMany a b a0 -> b0 #

foldl :: (b0 -> a0 -> b0) -> b0 -> BimapMany a b a0 -> b0 #

foldl' :: (b0 -> a0 -> b0) -> b0 -> BimapMany a b a0 -> b0 #

foldr1 :: (a0 -> a0 -> a0) -> BimapMany a b a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> BimapMany a b a0 -> a0 #

toList :: BimapMany a b a0 -> [a0] #

null :: BimapMany a b a0 -> Bool #

length :: BimapMany a b a0 -> Int #

elem :: Eq a0 => a0 -> BimapMany a b a0 -> Bool #

maximum :: Ord a0 => BimapMany a b a0 -> a0 #

minimum :: Ord a0 => BimapMany a b a0 -> a0 #

sum :: Num a0 => BimapMany a b a0 -> a0 #

product :: Num a0 => BimapMany a b a0 -> a0 #

Traversable (BimapMany a b) Source # 
Instance details

Defined in Data.BimapMany

Methods

traverse :: Applicative f => (a0 -> f b0) -> BimapMany a b a0 -> f (BimapMany a b b0) #

sequenceA :: Applicative f => BimapMany a b (f a0) -> f (BimapMany a b a0) #

mapM :: Monad m => (a0 -> m b0) -> BimapMany a b a0 -> m (BimapMany a b b0) #

sequence :: Monad m => BimapMany a b (m a0) -> m (BimapMany a b a0) #

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

Defined in Data.BimapMany

Methods

(==) :: BimapMany a b c -> BimapMany a b c -> Bool #

(/=) :: BimapMany a b c -> BimapMany a b c -> Bool #

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

Defined in Data.BimapMany

Methods

compare :: BimapMany a b c -> BimapMany a b c -> Ordering #

(<) :: BimapMany a b c -> BimapMany a b c -> Bool #

(<=) :: BimapMany a b c -> BimapMany a b c -> Bool #

(>) :: BimapMany a b c -> BimapMany a b c -> Bool #

(>=) :: BimapMany a b c -> BimapMany a b c -> Bool #

max :: BimapMany a b c -> BimapMany a b c -> BimapMany a b c #

min :: BimapMany a b c -> BimapMany a b c -> BimapMany a b c #

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

Defined in Data.BimapMany

Methods

showsPrec :: Int -> BimapMany a b c -> ShowS #

show :: BimapMany a b c -> String #

showList :: [BimapMany a b c] -> ShowS #

Generic (BimapMany a b c) Source # 
Instance details

Defined in Data.BimapMany

Associated Types

type Rep (BimapMany a b c) :: Type -> Type #

Methods

from :: BimapMany a b c -> Rep (BimapMany a b c) x #

to :: Rep (BimapMany a b c) x -> BimapMany a b c #

(Ord a, Ord b) => Semigroup (BimapMany a b c) Source # 
Instance details

Defined in Data.BimapMany

Methods

(<>) :: BimapMany a b c -> BimapMany a b c -> BimapMany a b c #

sconcat :: NonEmpty (BimapMany a b c) -> BimapMany a b c #

stimes :: Integral b0 => b0 -> BimapMany a b c -> BimapMany a b c #

(Ord a, Ord b) => Monoid (BimapMany a b c) Source # 
Instance details

Defined in Data.BimapMany

Methods

mempty :: BimapMany a b c #

mappend :: BimapMany a b c -> BimapMany a b c -> BimapMany a b c #

mconcat :: [BimapMany a b c] -> BimapMany a b c #

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

Defined in Data.BimapMany

Methods

rnf :: BimapMany a b c -> () #

type Rep (BimapMany a b c) Source # 
Instance details

Defined in Data.BimapMany

type Rep (BimapMany a b c) = D1 ('MetaData "BimapMany" "Data.BimapMany" "bimap-many-0.1.0.0-inplace-bimap-indef-BbjAm86NTDf8X7X6KvI6sA" 'False) (C1 ('MetaCons "BimapMany" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map a (Set b))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map b (Set a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (a, b) c)))))

Construction

singleton :: a -> b -> c -> BimapMany a b c Source #

fromMap :: (Ord a, Ord b) => Map (a, b) c -> BimapMany a b c Source #

fromSet :: (Ord a, Ord b) => (a -> b -> c) -> Set (a, b) -> BimapMany a b c Source #

From unordered lists

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

Insertion

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

Deletion/Update

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

deleteL :: (Ord a, Ord b) => a -> BimapMany a b c -> BimapMany a b c Source #

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

Query

Lookup

lookup :: (Ord a, Ord b) => a -> b -> BimapMany a b c -> Maybe c Source #

lookupL :: Ord a => a -> BimapMany a b c -> Set b Source #

lookupR :: Ord b => b -> BimapMany a b c -> Set a Source #

lookupL' :: (Ord a, Ord b) => a -> BimapMany a b c -> Map b c Source #

lookupR' :: (Ord a, Ord b) => b -> BimapMany a b c -> Map a c Source #

Size

null :: BimapMany a b c -> Bool Source #

size :: BimapMany a b c -> Int Source #

sizeL :: BimapMany a b c -> Int Source #

sizeR :: BimapMany a b c -> Int Source #

Combine

union :: (Ord a, Ord b) => BimapMany a b c -> BimapMany a b c -> BimapMany a b c Source #

Conversion

Maps

toMap :: BimapMany a b c -> Map (a, b) c Source #

Lists

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

Debugging

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