Safe Haskell | None |
---|---|
Language | Haskell2010 |
Warning: This module should be considered highly experimental.
- class (Monoid set, Semigroup set, MonoFoldable set, Eq (ContainerKey set), GrowingAppend set) => SetContainer set where
- type ContainerKey set
- class PolyMap map where
- class BiPolyMap map where
- type BPMKeyConstraint map key :: Constraint
- class (MonoTraversable map, SetContainer map) => IsMap map where
- type MapValue map
- class (SetContainer set, Element set ~ ContainerKey set) => IsSet set where
- class MonoFunctor mono => MonoZip mono where
- class SetContainer set => HasKeysSet set where
- type KeySet set
Documentation
class (Monoid set, Semigroup set, MonoFoldable set, Eq (ContainerKey set), GrowingAppend set) => SetContainer set where Source #
A container whose values are stored in Key-Value pairs.
type ContainerKey set Source #
The type of the key
member :: ContainerKey set -> set -> Bool Source #
Check if there is a value with the supplied key in the container.
notMember :: ContainerKey set -> set -> Bool Source #
Check if there isn't a value with the supplied key in the container.
union :: set -> set -> set Source #
Get the union of two containers.
unions :: (MonoFoldable mono, Element mono ~ set) => mono -> set Source #
Combine a collection of SetContainer
s, with left-most values overriding
when there are matching keys.
Since: 1.0.0
difference :: set -> set -> set Source #
Get the difference of two containers.
intersection :: set -> set -> set Source #
Get the intersection of two containers.
keys :: set -> [ContainerKey set] Source #
Get a list of all of the keys in the container.
SetContainer IntSet Source # | |
Eq key => SetContainer [(key, value)] Source # | |
SetContainer (IntMap value) Source # | This instance uses the functions from Data.IntMap.Strict. |
Ord element => SetContainer (Set element) Source # | |
(Eq element, Hashable element) => SetContainer (HashSet element) Source # | |
Ord k => SetContainer (Map k v) Source # | This instance uses the functions from Data.Map.Strict. |
(Eq key, Hashable key) => SetContainer (HashMap key value) Source # | This instance uses the functions from Data.HashMap.Strict. |
class PolyMap map where Source #
A guaranteed-polymorphic Map
, which allows for more polymorphic versions
of functions.
differenceMap :: map value1 -> map value2 -> map value1 Source #
Get the difference between two maps, using the left map's values.
intersectionMap :: map value1 -> map value2 -> map value1 Source #
Get the intersection of two maps, using the left map's values.
intersectionWithMap :: (value1 -> value2 -> value3) -> map value1 -> map value2 -> map value3 Source #
Get the intersection of two maps with a supplied function that takes in the left map's value and the right map's value.
class BiPolyMap map where Source #
A Map
type polymorphic in both its key and value.
type BPMKeyConstraint map key :: Constraint Source #
mapKeysWith :: (BPMKeyConstraint map k1, BPMKeyConstraint map k2) => (v -> v -> v) -> (k1 -> k2) -> map k1 v -> map k2 v Source #
class (MonoTraversable map, SetContainer map) => IsMap map where Source #
Polymorphic typeclass for interacting with different map types
lookup :: ContainerKey map -> map -> Maybe (MapValue map) Source #
Look up a value in a map with a specified key.
insertMap :: ContainerKey map -> MapValue map -> map -> map Source #
Insert a key-value pair into a map.
deleteMap :: ContainerKey map -> map -> map Source #
Delete a key-value pair of a map using a specified key.
singletonMap :: ContainerKey map -> MapValue map -> map Source #
Create a map from a single key-value pair.
mapFromList :: [(ContainerKey map, MapValue map)] -> map Source #
Convert a list of key-value pairs to a map
mapToList :: map -> [(ContainerKey map, MapValue map)] Source #
Convert a map to a list of key-value pairs.
findWithDefault :: MapValue map -> ContainerKey map -> map -> MapValue map Source #
Like lookup
, but uses a default value when the key does
not exist in the map.
insertWith :: (MapValue map -> MapValue map -> MapValue map) -> ContainerKey map -> MapValue map -> map -> map Source #
Insert a key-value pair into a map.
Inserts the value directly if the key does not exist in the map. Otherwise, apply a supplied function that accepts the new value and the previous value and insert that result into the map.
insertWithKey :: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) -> ContainerKey map -> MapValue map -> map -> map Source #
Insert a key-value pair into a map.
Inserts the value directly if the key does not exist in the map. Otherwise, apply a supplied function that accepts the key, the new value, and the previous value and insert that result into the map.
insertLookupWithKey :: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) -> ContainerKey map -> MapValue map -> map -> (Maybe (MapValue map), map) Source #
Insert a key-value pair into a map, return the previous key's value if it existed.
Inserts the value directly if the key does not exist in the map. Otherwise, apply a supplied function that accepts the key, the new value, and the previous value and insert that result into the map.
adjustMap :: (MapValue map -> MapValue map) -> ContainerKey map -> map -> map Source #
Apply a function to the value of a given key.
Returns the input map when the key-value pair does not exist.
adjustWithKey :: (ContainerKey map -> MapValue map -> MapValue map) -> ContainerKey map -> map -> map Source #
Equivalent to adjustMap
, but the function accepts the key,
as well as the previous value.
updateMap :: (MapValue map -> Maybe (MapValue map)) -> ContainerKey map -> map -> map Source #
Apply a function to the value of a given key.
If the function returns Nothing
, this deletes the key-value pair.
Returns the input map when the key-value pair does not exist.
updateWithKey :: (ContainerKey map -> MapValue map -> Maybe (MapValue map)) -> ContainerKey map -> map -> map Source #
Equivalent to updateMap
, but the function accepts the key,
as well as the previous value.
updateLookupWithKey :: (ContainerKey map -> MapValue map -> Maybe (MapValue map)) -> ContainerKey map -> map -> (Maybe (MapValue map), map) Source #
Apply a function to the value of a given key.
If the map does not contain the key this returns Nothing
and the input map.
If the map does contain the key but the function returns Nothing
,
this returns the previous value and the map with the key-value pair removed.
If the map contains the key and the function returns a value, this returns the new value and the map with the key-value pair with the new value.
alterMap :: (Maybe (MapValue map) -> Maybe (MapValue map)) -> ContainerKey map -> map -> map Source #
Update/Delete the value of a given key.
Applies a function to previous value of a given key, if it results in Nothing
delete the key-value pair from the map, otherwise replace the previous value
with the new value.
unionWith :: (MapValue map -> MapValue map -> MapValue map) -> map -> map -> map Source #
Combine two maps.
When a key exists in both maps, apply a function to both of the values and use the result of that as the value of the key in the resulting map.
unionWithKey :: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) -> map -> map -> map Source #
unionsWith :: (MapValue map -> MapValue map -> MapValue map) -> [map] -> map Source #
Combine a list of maps.
When a key exists in two different maps, apply a function to both of the values and use the result of that as the value of the key in the resulting map.
mapWithKey :: (ContainerKey map -> MapValue map -> MapValue map) -> map -> map Source #
Apply a function over every key-value pair of a map.
omapKeysWith :: (MapValue map -> MapValue map -> MapValue map) -> (ContainerKey map -> ContainerKey map) -> map -> map Source #
Apply a function over every key of a pair and run
unionsWith
over the results.
Eq key => IsMap [(key, value)] Source # | |
IsMap (IntMap value) Source # | This instance uses the functions from Data.IntMap.Strict. |
Ord key => IsMap (Map key value) Source # | This instance uses the functions from Data.Map.Strict. |
(Eq key, Hashable key) => IsMap (HashMap key value) Source # | This instance uses the functions from Data.HashMap.Strict. |
class (SetContainer set, Element set ~ ContainerKey set) => IsSet set where Source #
Polymorphic typeclass for interacting with different set types
insertSet :: Element set -> set -> set Source #
Insert a value into a set.
deleteSet :: Element set -> set -> set Source #
Delete a value from a set.
singletonSet :: Element set -> set Source #
Create a set from a single element.
setFromList :: [Element set] -> set Source #
Convert a list to a set.
setToList :: set -> [Element set] Source #
Convert a set to a list.
class MonoFunctor mono => MonoZip mono where Source #
Zip operations on MonoFunctor
s.
ozipWith :: (Element mono -> Element mono -> Element mono) -> mono -> mono -> mono Source #
Combine each element of two MonoZip
s using a supplied function.
ozip :: mono -> mono -> [(Element mono, Element mono)] Source #
Take two MonoZip
s and return a list of the pairs of their elements.
ounzip :: [(Element mono, Element mono)] -> (mono, mono) Source #
class SetContainer set => HasKeysSet set where Source #
Type class for maps whose keys can be converted into sets.
HasKeysSet (IntMap v) Source # | |
Ord k => HasKeysSet (Map k v) Source # | |
(Hashable k, Eq k) => HasKeysSet (HashMap k v) Source # | |