Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data.Map.Class
Synopsis
- class Traversable map => StaticMap map where
- type Key map
- adjustA :: Applicative p => (a -> p a) -> Key map -> map a -> p (map a)
- traverseWithKey :: Applicative p => (Key map -> a -> p b) -> map a -> p (map b)
- class (Filtrable map, StaticMap map) => Map map where
- empty :: map a
- alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key map -> map a -> f (map a)
- mergeA :: Applicative p => (Key map -> Either' a b -> p (Maybe c)) -> map a -> map b -> p (map c)
- mapMaybeWithKeyA :: Applicative p => (Key map -> a -> p (Maybe b)) -> map a -> p (map b)
- mapEitherWithKeyA :: Applicative p => (Key map -> a -> p (Either b c)) -> map a -> p (map b, map c)
- defaultAdjustA :: (Map map, Applicative p) => (a -> p a) -> Key map -> map a -> p (map a)
- defaultTraverseWithKey :: (Map map, Applicative p) => (Key map -> a -> p b) -> map a -> p (map b)
- (!?) :: StaticMap map => map a -> Key map -> Maybe a
- insert :: Map map => Key map -> a -> map a -> map a
- insertWith :: Map map => (a -> a -> a) -> Key map -> a -> map a -> map a
- insertLookup :: Map map => Key map -> a -> map a -> (Maybe a, map a)
- insertLookupWith :: Map map => (a -> a -> a) -> Key map -> a -> map a -> (Maybe a, map a)
- delete :: Map map => Key map -> map a -> map a
- adjust :: StaticMap map => (a -> a) -> Key map -> map a -> map a
- update :: Map map => (a -> Maybe a) -> Key map -> map a -> map a
- updateLookup :: Map map => (a -> Maybe a) -> Key map -> map a -> (Maybe a, map a)
- alter :: Map map => (Maybe a -> Maybe a) -> Key map -> map a -> map a
- alterLookup :: Map map => (Maybe a -> Maybe a) -> Key map -> map a -> (Maybe a, map a)
- alterLookupF :: (Map map, Functor f) => (Maybe a -> f (Maybe a)) -> Key map -> map a -> f (Maybe a, map a)
- mapWithKey :: StaticMap map => (Key map -> a -> b) -> map a -> map b
- mapMaybeWithKey :: Map map => (Key map -> a -> Maybe b) -> map a -> map b
- mapEitherWithKey :: Map map => (Key map -> a -> Either b c) -> map a -> (map b, map c)
- foldMapWithKeyA :: (StaticMap map, Applicative p, Monoid b) => (Key map -> a -> p b) -> map a -> p b
- foldrWithKeyM :: (StaticMap map, Monad m) => (Key map -> a -> b -> m b) -> b -> map a -> m b
- foldlWithKeyM :: (StaticMap map, Monad m) => (b -> Key map -> a -> m b) -> b -> map a -> m b
- foldMapWithKey :: (StaticMap map, Monoid b) => (Key map -> a -> b) -> map a -> b
- foldrWithKey :: StaticMap map => (Key map -> a -> b -> b) -> b -> map a -> b
- foldlWithKey :: StaticMap map => (b -> Key map -> a -> b) -> b -> map a -> b
- fromList :: Map map => [(Key map, a)] -> map a
- fromListWith :: Map map => (a -> a -> a) -> [(Key map, a)] -> map a
- fromListWithKey :: Map map => (Key map -> a -> a -> a) -> [(Key map, a)] -> map a
- fromListWithM :: (Map map, Monad m) => (a -> a -> m a) -> [(Key map, a)] -> m (map a)
- fromListWithKeyM :: (Map map, Monad m) => (Key map -> a -> a -> m a) -> [(Key map, a)] -> m (map a)
- adjustLookupA :: (StaticMap map, Applicative p) => (a -> p a) -> Key map -> map a -> p (Maybe a, map a)
- singleton :: Map map => Key map -> a -> map a
- unionWith :: Map map => (Key map -> a -> a -> a) -> map a -> map a -> map a
- intersectionWith :: Map map => (Key map -> a -> b -> c) -> map a -> map b -> map c
- merge :: Map map => (Key map -> Either' a b -> Maybe c) -> map a -> map b -> map c
- unionWithA :: (Map map, Applicative p) => (Key map -> a -> a -> p a) -> map a -> map a -> p (map a)
- intersectionWithA :: (Map map, Applicative p) => (Key map -> a -> b -> p c) -> map a -> map b -> p (map c)
- difference :: Map map => map a -> map b -> map a
- symmetricDifference :: Map map => map a -> map a -> map a
- mapKeys :: (StaticMap m, Map n) => (Key m -> Key n) -> m a -> n a
- mapKeysWith :: (StaticMap m, Map n) => (a -> a -> a) -> (Key m -> Key n) -> m a -> n a
- traverseKeys :: (StaticMap m, Map n, Applicative p) => (Key m -> p (Key n)) -> m a -> p (n a)
- traverseKeysWith :: (StaticMap m, Map n, Applicative p) => (a -> a -> a) -> (Key m -> p (Key n)) -> m a -> p (n a)
- mapKeysMaybe :: (StaticMap m, Map n) => (Key m -> Maybe (Key n)) -> m a -> n a
- mapKeysMaybeWith :: (StaticMap m, Map n) => (a -> a -> a) -> (Key m -> Maybe (Key n)) -> m a -> n a
- traverseKeysMaybe :: (StaticMap m, Map n, Applicative p) => (Key m -> p (Maybe (Key n))) -> m a -> p (n a)
- traverseKeysMaybeWith :: (StaticMap m, Map n, Applicative p) => (a -> a -> a) -> (Key m -> p (Maybe (Key n))) -> m a -> p (n a)
- keys :: StaticMap map => map a -> map (Key map)
- newtype Union map a = Union {
- unUnion :: map a
- newtype Intersection map a = Intersection {
- unIntersection :: map a
- newtype SymmetricDifference map a = SymmetricDifference {
- unSymmetricDifference :: map a
Documentation
class Traversable map => StaticMap map where Source #
Class of key-value maps
Laws:
Methods
adjustA :: Applicative p => (a -> p a) -> Key map -> map a -> p (map a) Source #
Modify the value of the key in the map. If the key is absent, the map is returned unmodified.
traverseWithKey :: Applicative p => (Key map -> a -> p b) -> map a -> p (map b) Source #
Traverse a function over each value in the map.
Instances
class (Filtrable map, StaticMap map) => Map map where Source #
Class of key-value maps with variable structure
Minimal complete definition
Methods
The empty map
alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key map -> map a -> f (map a) Source #
Modify the value of the key in the map, or insert the key and its value into the map, or delete the key and its value from the map, functorially.
fmap (!?
k) .alterF
f k = f . (!?
k)
This is the most general operation on a given key in the map.
mergeA :: Applicative p => (Key map -> Either' a b -> p (Maybe c)) -> map a -> map b -> p (map c) Source #
Combine two maps with the given function, which is called once for each key present in either map, inclusive.
mapMaybeWithKeyA :: Applicative p => (Key map -> a -> p (Maybe b)) -> map a -> p (map b) Source #
Traverse a function over each value in the map, gathering the Just
values and forgetting the Nothing
.
mapEitherWithKeyA :: Applicative p => (Key map -> a -> p (Either b c)) -> map a -> p (map b, map c) Source #
Instances
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 #
Default implementation of traverseWithKey
in terms of Map
methods
insert :: Map map => Key map -> a -> map a -> map a Source #
Insert a key and new value into the map, the new value clobbering the old if the key is already present.
insert
= insertWith
pure
insertWith :: Map map => (a -> a -> a) -> Key map -> a -> map a -> map a Source #
Insert a key and new value into the map, combining the old and new values with the given function if the key is already present.
insertLookup :: Map map => Key map -> a -> map a -> (Maybe a, map a) Source #
Insert a key and new value into the map, looking up the old value if the key is already present.
insertLookupWith :: Map map => (a -> a -> a) -> Key map -> a -> map a -> (Maybe a, map a) Source #
Insert a key and new value into the map, looking up the old value and combining the old and new values with the given function if the key is already present.
delete :: Map map => Key map -> map a -> map a Source #
Delete a key and its value from the map. If the key is absent, the map is returned unmodified.
adjust :: StaticMap map => (a -> a) -> Key map -> map a -> map a Source #
Modify the value of the key in the map. If the key is absent, the map is returned unmodified.
alter :: Map map => (Maybe a -> Maybe a) -> Key map -> map a -> map a Source #
Modify the value of the key in the map, or insert the key and its value into the map, or delete the key and its value from the map.
alterLookup :: Map map => (Maybe a -> Maybe a) -> Key map -> map a -> (Maybe a, map a) Source #
Modify the value of the key in the map, or insert the key and its value into the map, or delete the key and its value from the map, looking up the old value if the key is already present.
alterLookupF :: (Map map, Functor f) => (Maybe a -> f (Maybe a)) -> Key map -> map a -> f (Maybe a, map a) Source #
Modify the value of the key in the map, or insert the key and its value into the map, or delete the key and its value from the map, looking up the old value if the key is already present, functorially.
This is no more general than alterF
, but is defined for convenience.
mapWithKey :: StaticMap map => (Key map -> a -> b) -> map a -> map b Source #
Map a function over each value in the map.
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 #
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 #
fromListWith :: Map map => (a -> a -> a) -> [(Key map, a)] -> 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 #
Modify the value of the key in the map, looking up the old value if the key is already present. If the key is absent, the map is returned unmodified.
unionWith :: Map map => (Key map -> a -> a -> a) -> map a -> map a -> map a Source #
Union of two maps, combining values of the same key with the given function
intersectionWith :: Map map => (Key map -> a -> b -> c) -> map a -> map b -> map c Source #
Intersection of two maps, combining values of the same key with the given function
merge :: Map map => (Key map -> Either' a b -> Maybe c) -> map a -> map b -> map c Source #
Combine two maps with the given function, which is called once for each key present in either map, inclusive.
unionWithA :: (Map map, Applicative p) => (Key map -> a -> a -> p a) -> map a -> map a -> p (map a) Source #
Union of two maps, combining values of the same key with the given function
intersectionWithA :: (Map map, Applicative p) => (Key map -> a -> b -> p c) -> map a -> map b -> p (map c) Source #
Intersection of two maps, combining values of the same key with the given function
difference :: Map map => map a -> map b -> map a Source #
Difference of two maps, which contains exactly the keys present in the first map but absent in the second
symmetricDifference :: Map map => map a -> map a -> map a Source #
Symmetric difference of two maps, which contains exactly the keys present in the either map but absent in the other
mapKeys :: (StaticMap m, Map n) => (Key m -> Key n) -> m a -> n a Source #
Map a function over each key in the map.
mapKeysWith :: (StaticMap m, Map n) => (a -> a -> a) -> (Key m -> Key n) -> m a -> n a Source #
Map a function over each key in the map, combining values of keys which collide with the given function.
traverseKeys :: (StaticMap m, Map n, Applicative p) => (Key m -> p (Key n)) -> m a -> p (n a) Source #
Traverse a function over each key in the map.
traverseKeysWith :: (StaticMap m, Map n, Applicative p) => (a -> a -> a) -> (Key m -> p (Key n)) -> m a -> p (n a) Source #
Traverse a function over each key in the map, combining values of keys which collide with the given function.
mapKeysMaybeWith :: (StaticMap m, Map n) => (a -> a -> a) -> (Key m -> Maybe (Key n)) -> m a -> n a Source #
traverseKeysMaybe :: (StaticMap m, Map n, Applicative p) => (Key m -> p (Maybe (Key n))) -> m a -> p (n a) Source #
traverseKeysMaybeWith :: (StaticMap m, Map n, Applicative p) => (a -> a -> a) -> (Key m -> p (Maybe (Key n))) -> m a -> p (n a) Source #
Wrapper of a Map
whose semigroup operation is the union, combining values elementwise, and ergo whose monoidal unit is empty
Instances
Functor map => Functor (Union map) Source # | |
Foldable map => Foldable (Union map) Source # | |
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] # 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 # | |
Traversable map => Traversable (Union map) Source # | |
Eq1 map => Eq1 (Union map) Source # | |
Ord1 map => Ord1 (Union map) Source # | |
Defined in Data.Map.Class | |
Read1 map => Read1 (Union map) Source # | |
Defined in Data.Map.Class | |
Show1 map => Show1 (Union map) Source # | |
Filtrable map => Filtrable (Union map) Source # | |
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 # | |
Defined in Data.Map.Class Methods 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 # | |
Eq (map a) => Eq (Union map a) Source # | |
Ord (map a) => Ord (Union map a) Source # | |
Defined in Data.Map.Class | |
Read (map a) => Read (Union map a) Source # | |
Show (map a) => Show (Union map a) Source # | |
(Map map, Semigroup a) => Semigroup (Union map a) Source # | |
(Map map, Semigroup a) => Monoid (Union map a) Source # | |
type Key (Union map) Source # | |
Defined in Data.Map.Class |
newtype Intersection map a Source #
Wrapper of a Map
whose semigroup operation is the intersection, combining values elementwise
Constructors
Intersection | |
Fields
|
Instances
newtype SymmetricDifference map a Source #
Wrapper of a Map
whose semigroup operation is the symmetric difference, and ergo whose monoidal unit is empty
Constructors
SymmetricDifference | |
Fields
|