Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data BimapMany a b c
- empty :: BimapMany a b c
- singleton :: a -> b -> c -> BimapMany a b c
- fromMap :: (Ord a, Ord b) => Map (a, b) c -> BimapMany a b c
- fromSet :: (Ord a, Ord b) => (a -> b -> c) -> Set (a, b) -> BimapMany a b c
- fromList :: (Ord a, Ord b) => [(a, b, c)] -> BimapMany a b c
- insert :: (Ord a, Ord b) => a -> b -> c -> BimapMany a b c -> BimapMany a b c
- delete :: (Ord a, Ord b) => a -> b -> BimapMany a b c -> BimapMany a b c
- deleteL :: (Ord a, Ord b) => a -> BimapMany a b c -> BimapMany a b c
- deleteR :: (Ord a, Ord b) => b -> BimapMany a b c -> BimapMany a b c
- lookup :: (Ord a, Ord b) => a -> b -> BimapMany a b c -> Maybe c
- lookupL :: Ord a => a -> BimapMany a b c -> Set b
- lookupR :: Ord b => b -> BimapMany a b c -> Set a
- lookupL' :: (Ord a, Ord b) => a -> BimapMany a b c -> Map b c
- lookupR' :: (Ord a, Ord b) => b -> BimapMany a b c -> Map a c
- null :: BimapMany a b c -> Bool
- size :: BimapMany a b c -> Int
- sizeL :: BimapMany a b c -> Int
- sizeR :: BimapMany a b c -> Int
- union :: (Ord a, Ord b) => BimapMany a b c -> BimapMany a b c -> BimapMany a b c
- toMap :: BimapMany a b c -> Map (a, b) c
- toList :: BimapMany a b c -> [(a, b, c)]
- valid :: (Ord a, Ord b) => BimapMany a b c -> Bool
BimapMany type
Instances
Functor (BimapMany a b) Source # | |
Foldable (BimapMany a b) Source # | |
Defined in Data.BimapMany 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 # | |
Traversable (BimapMany a b) Source # | |
Defined in Data.BimapMany 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 # | |
(Ord a, Ord b, Ord c) => Ord (BimapMany a b c) Source # | |
Defined in Data.BimapMany 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 # | |
Generic (BimapMany a b c) Source # | |
(Ord a, Ord b) => Semigroup (BimapMany a b c) Source # | |
(Ord a, Ord b) => Monoid (BimapMany a b c) Source # | |
(NFData a, NFData b, NFData c) => NFData (BimapMany a b c) Source # | |
Defined in Data.BimapMany | |
type Rep (BimapMany a b c) Source # | |
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))))) |