Map-0.1.2.0: Class of key-value maps

Safe HaskellNone
LanguageHaskell2010

Data.Map.Class

Contents

Synopsis

Documentation

class Traversable map => StaticMap map where Source #

Associated Types

type Key map Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key map -> map a -> p (map a) Source #

traverseWithKey :: Applicative p => (Key map -> a -> p b) -> map a -> p (map b) Source #

Instances
StaticMap Maybe Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key Maybe :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key Maybe -> Maybe a -> p (Maybe a) Source #

traverseWithKey :: Applicative p => (Key Maybe -> a -> p b) -> Maybe a -> p (Maybe b) Source #

StaticMap IntMap Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key IntMap :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key IntMap -> IntMap a -> p (IntMap a) Source #

traverseWithKey :: Applicative p => (Key IntMap -> a -> p b) -> IntMap a -> p (IntMap b) Source #

Ord key => StaticMap (Map key) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Map key) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Map key) -> Map key a -> p (Map key a) Source #

traverseWithKey :: Applicative p => (Key (Map key) -> a -> p b) -> Map key a -> p (Map key b) Source #

StaticMap map => StaticMap (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (SymmetricDifference map) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (SymmetricDifference map) -> SymmetricDifference map a -> p (SymmetricDifference map a) Source #

traverseWithKey :: Applicative p => (Key (SymmetricDifference map) -> a -> p b) -> SymmetricDifference map a -> p (SymmetricDifference map b) Source #

StaticMap map => StaticMap (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Intersection map) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Intersection map) -> Intersection map a -> p (Intersection map a) Source #

traverseWithKey :: Applicative p => (Key (Intersection map) -> a -> p b) -> Intersection map a -> p (Intersection map b) Source #

StaticMap map => StaticMap (Union map) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Union map) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Union map) -> Union map a -> p (Union map a) Source #

traverseWithKey :: Applicative p => (Key (Union map) -> a -> p b) -> Union map a -> p (Union map b) Source #

(StaticMap m, StaticMap n) => StaticMap (Product m n) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Product m n) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Product m n) -> Product m n a -> p (Product m n a) Source #

traverseWithKey :: Applicative p => (Key (Product m n) -> a -> p b) -> Product m n a -> p (Product m n b) Source #

(StaticMap m, StaticMap n) => StaticMap (Compose m n) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Compose m n) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Compose m n) -> Compose m n a -> p (Compose m n a) Source #

traverseWithKey :: Applicative p => (Key (Compose m n) -> a -> p b) -> Compose m n a -> p (Compose m n b) Source #

class (Filtrable map, StaticMap map) => Map map where Source #

Minimal complete definition

empty, alterF, mergeA, mapMaybeWithKeyA

Methods

empty :: map a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key map -> map a -> f (map a) Source #

mergeA :: Applicative p => (Key map -> Either' a b -> p (Maybe c)) -> map a -> map b -> p (map c) Source #

mapMaybeWithKeyA :: Applicative p => (Key map -> a -> p (Maybe b)) -> map a -> p (map b) Source #

mapEitherWithKeyA :: Applicative p => (Key map -> a -> p (Either b c)) -> map a -> p (map b, map c) Source #

Instances
Map Maybe Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Maybe a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key Maybe -> Maybe a -> f (Maybe a) Source #

mergeA :: Applicative p => (Key Maybe -> Either' a b -> p (Maybe c)) -> Maybe a -> Maybe b -> p (Maybe c) Source #

mapMaybeWithKeyA :: Applicative p => (Key Maybe -> a -> p (Maybe b)) -> Maybe a -> p (Maybe b) Source #

mapEitherWithKeyA :: Applicative p => (Key Maybe -> a -> p (Either b c)) -> Maybe a -> p (Maybe b, Maybe c) Source #

Map IntMap Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: IntMap a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key IntMap -> IntMap a -> f (IntMap a) Source #

mergeA :: Applicative p => (Key IntMap -> Either' a b -> p (Maybe c)) -> IntMap a -> IntMap b -> p (IntMap c) Source #

mapMaybeWithKeyA :: Applicative p => (Key IntMap -> a -> p (Maybe b)) -> IntMap a -> p (IntMap b) Source #

mapEitherWithKeyA :: Applicative p => (Key IntMap -> a -> p (Either b c)) -> IntMap a -> p (IntMap b, IntMap c) Source #

Ord key => Map (Map key) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Map key a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Map key) -> Map key a -> f (Map key a) Source #

mergeA :: Applicative p => (Key (Map key) -> Either' a b -> p (Maybe c)) -> Map key a -> Map key b -> p (Map key c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Map key) -> a -> p (Maybe b)) -> Map key a -> p (Map key b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Map key) -> a -> p (Either b c)) -> Map key a -> p (Map key b, Map key c) Source #

Map map => Map (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Map map => Map (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Intersection map a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Intersection map) -> Intersection map a -> f (Intersection map a) Source #

mergeA :: Applicative p => (Key (Intersection map) -> Either' a b -> p (Maybe c)) -> Intersection map a -> Intersection map b -> p (Intersection map c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Intersection map) -> a -> p (Maybe b)) -> Intersection map a -> p (Intersection map b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Intersection map) -> a -> p (Either b c)) -> Intersection map a -> p (Intersection map b, Intersection map c) Source #

Map map => Map (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Union map a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Union map) -> Union map a -> f (Union map a) Source #

mergeA :: Applicative p => (Key (Union map) -> Either' a b -> p (Maybe c)) -> Union map a -> Union map b -> p (Union map c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Union map) -> a -> p (Maybe b)) -> Union map a -> p (Union map b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Union map) -> a -> p (Either b c)) -> Union map a -> p (Union map b, Union map c) Source #

(Map m, Map n) => Map (Product m n) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Product m n a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Product m n) -> Product m n a -> f (Product m n a) Source #

mergeA :: Applicative p => (Key (Product m n) -> Either' a b -> p (Maybe c)) -> Product m n a -> Product m n b -> p (Product m n c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Product m n) -> a -> p (Maybe b)) -> Product m n a -> p (Product m n b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Product m n) -> a -> p (Either b c)) -> Product m n a -> p (Product m n b, Product m n c) Source #

(Map m, Map n) => Map (Compose m n) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Compose m n a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Compose m n) -> Compose m n a -> f (Compose m n a) Source #

mergeA :: Applicative p => (Key (Compose m n) -> Either' a b -> p (Maybe c)) -> Compose m n a -> Compose m n b -> p (Compose m n c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Compose m n) -> a -> p (Maybe b)) -> Compose m n a -> p (Compose m n b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Compose m n) -> a -> p (Either b c)) -> Compose m n a -> p (Compose m n b, Compose m n c) Source #

defaultAdjustA :: (Map map, Applicative p) => (a -> p a) -> Key map -> map a -> p (map a) Source #

defaultTraverseWithKey :: (Map map, Applicative p) => (Key map -> a -> p b) -> map a -> p (map b) Source #

(!?) :: StaticMap map => map a -> Key map -> Maybe a infix 9 Source #

insert :: Map map => Key map -> a -> map a -> map a Source #

insertWith :: Map map => (a -> a -> a) -> Key map -> a -> map a -> map a Source #

insertLookup :: Map map => Key map -> a -> map a -> (Maybe a, map a) Source #

insertLookupWith :: Map map => (a -> a -> a) -> Key map -> a -> map a -> (Maybe a, map a) Source #

delete :: Map map => Key map -> map a -> map a Source #

adjust :: StaticMap map => (a -> a) -> Key map -> map a -> map a Source #

update :: Map map => (a -> Maybe a) -> Key map -> map a -> map a Source #

updateLookup :: Map map => (a -> Maybe a) -> Key map -> map a -> (Maybe a, map a) Source #

alter :: Map map => (Maybe a -> Maybe a) -> Key map -> map a -> map a Source #

alterLookup :: Map map => (Maybe a -> Maybe a) -> Key map -> map a -> (Maybe a, map a) Source #

alterLookupF :: (Map map, Functor f) => (Maybe a -> f (Maybe a)) -> Key map -> map a -> f (Maybe a, map a) Source #

mapWithKey :: StaticMap map => (Key map -> a -> b) -> map a -> map b Source #

mapMaybeWithKey :: Map map => (Key map -> a -> Maybe b) -> map a -> map b Source #

mapEitherWithKey :: Map map => (Key map -> a -> Either b c) -> map a -> (map b, map c) Source #

foldMapWithKeyA :: (StaticMap map, Applicative p, Monoid b) => (Key map -> a -> p b) -> map a -> p b Source #

foldrWithKeyM :: (StaticMap map, Monad m) => (Key map -> a -> b -> m b) -> b -> map a -> m b Source #

foldlWithKeyM :: (StaticMap map, Monad m) => (b -> Key map -> a -> m b) -> b -> map a -> m b Source #

foldMapWithKey :: (StaticMap map, Monoid b) => (Key map -> a -> b) -> map a -> b Source #

foldrWithKey :: StaticMap map => (Key map -> a -> b -> b) -> b -> map a -> b Source #

foldlWithKey :: StaticMap map => (b -> Key map -> a -> b) -> b -> map a -> b Source #

fromList :: Map map => [(Key map, a)] -> map a Source #

fromListWith :: Map map => (a -> a -> a) -> [(Key map, a)] -> map a Source #

fromListWithKey :: Map map => (Key map -> a -> a -> a) -> [(Key map, a)] -> map a Source #

fromListWithM :: (Map map, Monad m) => (a -> a -> m a) -> [(Key map, a)] -> m (map a) Source #

fromListWithKeyM :: (Map map, Monad m) => (Key map -> a -> a -> m a) -> [(Key map, a)] -> m (map a) Source #

adjustLookupA :: (StaticMap map, Applicative p) => (a -> p a) -> Key map -> map a -> p (Maybe a, map a) Source #

singleton :: Map map => Key map -> a -> map a Source #

unionWith :: Map map => (Key map -> a -> a -> a) -> map a -> map a -> map a Source #

intersectionWith :: Map map => (Key map -> a -> b -> c) -> map a -> map b -> map c Source #

merge :: Map map => (Key map -> Either' a b -> Maybe c) -> map a -> map b -> map c Source #

unionWithA :: (Map map, Applicative p) => (Key map -> a -> a -> p a) -> map a -> map a -> p (map a) Source #

intersectionWithA :: (Map map, Applicative p) => (Key map -> a -> b -> p c) -> map a -> map b -> p (map c) Source #

difference :: Map map => map a -> map b -> map a Source #

symmetricDifference :: Map map => map a -> map a -> map a Source #

mapKeys :: (StaticMap m, Map n) => (Key m -> Key n) -> m a -> n a Source #

traverseKeys :: (StaticMap m, Map n, Applicative p) => (Key m -> p (Key n)) -> m a -> p (n a) Source #

keys :: StaticMap map => map a -> map (Key map) Source #

newtype Union map a Source #

Constructors

Union 

Fields

Instances
Functor map => Functor (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

fmap :: (a -> b) -> Union map a -> Union map b #

(<$) :: a -> Union map b -> Union map a #

Foldable map => Foldable (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

fold :: Monoid m => Union map m -> m #

foldMap :: Monoid m => (a -> m) -> Union map a -> m #

foldr :: (a -> b -> b) -> b -> Union map a -> b #

foldr' :: (a -> b -> b) -> b -> Union map a -> b #

foldl :: (b -> a -> b) -> b -> Union map a -> b #

foldl' :: (b -> a -> b) -> b -> Union map a -> b #

foldr1 :: (a -> a -> a) -> Union map a -> a #

foldl1 :: (a -> a -> a) -> Union map a -> a #

toList :: Union map a -> [a] #

null :: Union map a -> Bool #

length :: Union map a -> Int #

elem :: Eq a => a -> Union map a -> Bool #

maximum :: Ord a => Union map a -> a #

minimum :: Ord a => Union map a -> a #

sum :: Num a => Union map a -> a #

product :: Num a => Union map a -> a #

Traversable map => Traversable (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

traverse :: Applicative f => (a -> f b) -> Union map a -> f (Union map b) #

sequenceA :: Applicative f => Union map (f a) -> f (Union map a) #

mapM :: Monad m => (a -> m b) -> Union map a -> m (Union map b) #

sequence :: Monad m => Union map (m a) -> m (Union map a) #

Eq1 map => Eq1 (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftEq :: (a -> b -> Bool) -> Union map a -> Union map b -> Bool #

Ord1 map => Ord1 (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftCompare :: (a -> b -> Ordering) -> Union map a -> Union map b -> Ordering #

Read1 map => Read1 (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Union map a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Union map a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Union map a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Union map a] #

Show1 map => Show1 (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Union map a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Union map a] -> ShowS #

Filtrable map => Filtrable (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

mapMaybe :: (a -> Maybe b) -> Union map a -> Union map b #

catMaybes :: Union map (Maybe a) -> Union map a #

filter :: (a -> Bool) -> Union map a -> Union map a #

mapMaybeA :: (Traversable (Union map), Applicative p) => (a -> p (Maybe b)) -> Union map a -> p (Union map b) #

filterA :: (Traversable (Union map), Applicative p) => (a -> p Bool) -> Union map a -> p (Union map a) #

mapEither :: (a -> Either b c) -> Union map a -> (Union map b, Union map c) #

mapEitherA :: (Traversable (Union map), Applicative p) => (a -> p (Either b c)) -> Union map a -> p (Union map b, Union map c) #

partitionEithers :: Union map (Either a b) -> (Union map a, Union map b) #

Map map => Map (Union map) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Union map a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Union map) -> Union map a -> f (Union map a) Source #

mergeA :: Applicative p => (Key (Union map) -> Either' a b -> p (Maybe c)) -> Union map a -> Union map b -> p (Union map c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Union map) -> a -> p (Maybe b)) -> Union map a -> p (Union map b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Union map) -> a -> p (Either b c)) -> Union map a -> p (Union map b, Union map c) Source #

StaticMap map => StaticMap (Union map) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Union map) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Union map) -> Union map a -> p (Union map a) Source #

traverseWithKey :: Applicative p => (Key (Union map) -> a -> p b) -> Union map a -> p (Union map b) Source #

Eq (map a) => Eq (Union map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

(==) :: Union map a -> Union map a -> Bool #

(/=) :: Union map a -> Union map a -> Bool #

Ord (map a) => Ord (Union map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

compare :: Union map a -> Union map a -> Ordering #

(<) :: Union map a -> Union map a -> Bool #

(<=) :: Union map a -> Union map a -> Bool #

(>) :: Union map a -> Union map a -> Bool #

(>=) :: Union map a -> Union map a -> Bool #

max :: Union map a -> Union map a -> Union map a #

min :: Union map a -> Union map a -> Union map a #

Read (map a) => Read (Union map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

readsPrec :: Int -> ReadS (Union map a) #

readList :: ReadS [Union map a] #

readPrec :: ReadPrec (Union map a) #

readListPrec :: ReadPrec [Union map a] #

Show (map a) => Show (Union map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

showsPrec :: Int -> Union map a -> ShowS #

show :: Union map a -> String #

showList :: [Union map a] -> ShowS #

(Map map, Semigroup a) => Semigroup (Union map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

(<>) :: Union map a -> Union map a -> Union map a #

sconcat :: NonEmpty (Union map a) -> Union map a #

stimes :: Integral b => b -> Union map a -> Union map a #

(Map map, Semigroup a) => Monoid (Union map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

mempty :: Union map a #

mappend :: Union map a -> Union map a -> Union map a #

mconcat :: [Union map a] -> Union map a #

type Key (Union map) Source # 
Instance details

Defined in Data.Map.Class

type Key (Union map) = Key map

newtype Intersection map a Source #

Constructors

Intersection 

Fields

Instances
Functor map => Functor (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

fmap :: (a -> b) -> Intersection map a -> Intersection map b #

(<$) :: a -> Intersection map b -> Intersection map a #

Foldable map => Foldable (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

fold :: Monoid m => Intersection map m -> m #

foldMap :: Monoid m => (a -> m) -> Intersection map a -> m #

foldr :: (a -> b -> b) -> b -> Intersection map a -> b #

foldr' :: (a -> b -> b) -> b -> Intersection map a -> b #

foldl :: (b -> a -> b) -> b -> Intersection map a -> b #

foldl' :: (b -> a -> b) -> b -> Intersection map a -> b #

foldr1 :: (a -> a -> a) -> Intersection map a -> a #

foldl1 :: (a -> a -> a) -> Intersection map a -> a #

toList :: Intersection map a -> [a] #

null :: Intersection map a -> Bool #

length :: Intersection map a -> Int #

elem :: Eq a => a -> Intersection map a -> Bool #

maximum :: Ord a => Intersection map a -> a #

minimum :: Ord a => Intersection map a -> a #

sum :: Num a => Intersection map a -> a #

product :: Num a => Intersection map a -> a #

Traversable map => Traversable (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

traverse :: Applicative f => (a -> f b) -> Intersection map a -> f (Intersection map b) #

sequenceA :: Applicative f => Intersection map (f a) -> f (Intersection map a) #

mapM :: Monad m => (a -> m b) -> Intersection map a -> m (Intersection map b) #

sequence :: Monad m => Intersection map (m a) -> m (Intersection map a) #

Eq1 map => Eq1 (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftEq :: (a -> b -> Bool) -> Intersection map a -> Intersection map b -> Bool #

Ord1 map => Ord1 (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftCompare :: (a -> b -> Ordering) -> Intersection map a -> Intersection map b -> Ordering #

Read1 map => Read1 (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Intersection map a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Intersection map a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Intersection map a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Intersection map a] #

Show1 map => Show1 (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Intersection map a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Intersection map a] -> ShowS #

Filtrable map => Filtrable (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

mapMaybe :: (a -> Maybe b) -> Intersection map a -> Intersection map b #

catMaybes :: Intersection map (Maybe a) -> Intersection map a #

filter :: (a -> Bool) -> Intersection map a -> Intersection map a #

mapMaybeA :: (Traversable (Intersection map), Applicative p) => (a -> p (Maybe b)) -> Intersection map a -> p (Intersection map b) #

filterA :: (Traversable (Intersection map), Applicative p) => (a -> p Bool) -> Intersection map a -> p (Intersection map a) #

mapEither :: (a -> Either b c) -> Intersection map a -> (Intersection map b, Intersection map c) #

mapEitherA :: (Traversable (Intersection map), Applicative p) => (a -> p (Either b c)) -> Intersection map a -> p (Intersection map b, Intersection map c) #

partitionEithers :: Intersection map (Either a b) -> (Intersection map a, Intersection map b) #

Map map => Map (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Methods

empty :: Intersection map a Source #

alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key (Intersection map) -> Intersection map a -> f (Intersection map a) Source #

mergeA :: Applicative p => (Key (Intersection map) -> Either' a b -> p (Maybe c)) -> Intersection map a -> Intersection map b -> p (Intersection map c) Source #

mapMaybeWithKeyA :: Applicative p => (Key (Intersection map) -> a -> p (Maybe b)) -> Intersection map a -> p (Intersection map b) Source #

mapEitherWithKeyA :: Applicative p => (Key (Intersection map) -> a -> p (Either b c)) -> Intersection map a -> p (Intersection map b, Intersection map c) Source #

StaticMap map => StaticMap (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (Intersection map) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (Intersection map) -> Intersection map a -> p (Intersection map a) Source #

traverseWithKey :: Applicative p => (Key (Intersection map) -> a -> p b) -> Intersection map a -> p (Intersection map b) Source #

Eq (map a) => Eq (Intersection map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

(==) :: Intersection map a -> Intersection map a -> Bool #

(/=) :: Intersection map a -> Intersection map a -> Bool #

Ord (map a) => Ord (Intersection map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

compare :: Intersection map a -> Intersection map a -> Ordering #

(<) :: Intersection map a -> Intersection map a -> Bool #

(<=) :: Intersection map a -> Intersection map a -> Bool #

(>) :: Intersection map a -> Intersection map a -> Bool #

(>=) :: Intersection map a -> Intersection map a -> Bool #

max :: Intersection map a -> Intersection map a -> Intersection map a #

min :: Intersection map a -> Intersection map a -> Intersection map a #

Read (map a) => Read (Intersection map a) Source # 
Instance details

Defined in Data.Map.Class

Show (map a) => Show (Intersection map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

showsPrec :: Int -> Intersection map a -> ShowS #

show :: Intersection map a -> String #

showList :: [Intersection map a] -> ShowS #

(Map map, Semigroup a) => Semigroup (Intersection map a) Source # 
Instance details

Defined in Data.Map.Class

Methods

(<>) :: Intersection map a -> Intersection map a -> Intersection map a #

sconcat :: NonEmpty (Intersection map a) -> Intersection map a #

stimes :: Integral b => b -> Intersection map a -> Intersection map a #

type Key (Intersection map) Source # 
Instance details

Defined in Data.Map.Class

type Key (Intersection map) = Key map

newtype SymmetricDifference map a Source #

Constructors

SymmetricDifference 

Fields

Instances
Functor map => Functor (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Methods

fmap :: (a -> b) -> SymmetricDifference map a -> SymmetricDifference map b #

(<$) :: a -> SymmetricDifference map b -> SymmetricDifference map a #

Foldable map => Foldable (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Methods

fold :: Monoid m => SymmetricDifference map m -> m #

foldMap :: Monoid m => (a -> m) -> SymmetricDifference map a -> m #

foldr :: (a -> b -> b) -> b -> SymmetricDifference map a -> b #

foldr' :: (a -> b -> b) -> b -> SymmetricDifference map a -> b #

foldl :: (b -> a -> b) -> b -> SymmetricDifference map a -> b #

foldl' :: (b -> a -> b) -> b -> SymmetricDifference map a -> b #

foldr1 :: (a -> a -> a) -> SymmetricDifference map a -> a #

foldl1 :: (a -> a -> a) -> SymmetricDifference map a -> a #

toList :: SymmetricDifference map a -> [a] #

null :: SymmetricDifference map a -> Bool #

length :: SymmetricDifference map a -> Int #

elem :: Eq a => a -> SymmetricDifference map a -> Bool #

maximum :: Ord a => SymmetricDifference map a -> a #

minimum :: Ord a => SymmetricDifference map a -> a #

sum :: Num a => SymmetricDifference map a -> a #

product :: Num a => SymmetricDifference map a -> a #

Traversable map => Traversable (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Methods

traverse :: Applicative f => (a -> f b) -> SymmetricDifference map a -> f (SymmetricDifference map b) #

sequenceA :: Applicative f => SymmetricDifference map (f a) -> f (SymmetricDifference map a) #

mapM :: Monad m => (a -> m b) -> SymmetricDifference map a -> m (SymmetricDifference map b) #

sequence :: Monad m => SymmetricDifference map (m a) -> m (SymmetricDifference map a) #

Eq1 map => Eq1 (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftEq :: (a -> b -> Bool) -> SymmetricDifference map a -> SymmetricDifference map b -> Bool #

Ord1 map => Ord1 (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftCompare :: (a -> b -> Ordering) -> SymmetricDifference map a -> SymmetricDifference map b -> Ordering #

Read1 map => Read1 (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Show1 map => Show1 (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SymmetricDifference map a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [SymmetricDifference map a] -> ShowS #

Filtrable map => Filtrable (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Map map => Map (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

StaticMap map => StaticMap (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

Associated Types

type Key (SymmetricDifference map) :: Type Source #

Methods

adjustA :: Applicative p => (a -> p a) -> Key (SymmetricDifference map) -> SymmetricDifference map a -> p (SymmetricDifference map a) Source #

traverseWithKey :: Applicative p => (Key (SymmetricDifference map) -> a -> p b) -> SymmetricDifference map a -> p (SymmetricDifference map b) Source #

Eq (map a) => Eq (SymmetricDifference map a) Source # 
Instance details

Defined in Data.Map.Class

Ord (map a) => Ord (SymmetricDifference map a) Source # 
Instance details

Defined in Data.Map.Class

Read (map a) => Read (SymmetricDifference map a) Source # 
Instance details

Defined in Data.Map.Class

Show (map a) => Show (SymmetricDifference map a) Source # 
Instance details

Defined in Data.Map.Class

Map map => Semigroup (SymmetricDifference map a) Source # 
Instance details

Defined in Data.Map.Class

Map map => Monoid (SymmetricDifference map a) Source # 
Instance details

Defined in Data.Map.Class

type Key (SymmetricDifference map) Source # 
Instance details

Defined in Data.Map.Class

type Key (SymmetricDifference map) = Key map

Orphan instances

Filtrable IntMap Source # 
Instance details

Methods

mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b #

catMaybes :: IntMap (Maybe a) -> IntMap a #

filter :: (a -> Bool) -> IntMap a -> IntMap a #

mapMaybeA :: (Traversable IntMap, Applicative p) => (a -> p (Maybe b)) -> IntMap a -> p (IntMap b) #

filterA :: (Traversable IntMap, Applicative p) => (a -> p Bool) -> IntMap a -> p (IntMap a) #

mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) #

mapEitherA :: (Traversable IntMap, Applicative p) => (a -> p (Either b c)) -> IntMap a -> p (IntMap b, IntMap c) #

partitionEithers :: IntMap (Either a b) -> (IntMap a, IntMap b) #

Filtrable (Map key) Source # 
Instance details

Methods

mapMaybe :: (a -> Maybe b) -> Map key a -> Map key b #

catMaybes :: Map key (Maybe a) -> Map key a #

filter :: (a -> Bool) -> Map key a -> Map key a #

mapMaybeA :: (Traversable (Map key), Applicative p) => (a -> p (Maybe b)) -> Map key a -> p (Map key b) #

filterA :: (Traversable (Map key), Applicative p) => (a -> p Bool) -> Map key a -> p (Map key a) #

mapEither :: (a -> Either b c) -> Map key a -> (Map key b, Map key c) #

mapEitherA :: (Traversable (Map key), Applicative p) => (a -> p (Either b c)) -> Map key a -> p (Map key b, Map key c) #

partitionEithers :: Map key (Either a b) -> (Map key a, Map key b) #