Safe Haskell | None |
---|---|
Language | Haskell2010 |
Warning: This module should be considered highly experimental.
Synopsis
- class (Monoid set, Semigroup set, MonoFoldable set, Eq (ContainerKey set), GrowingAppend set) => SetContainer set where
- type ContainerKey set
- member :: ContainerKey set -> set -> Bool
- notMember :: ContainerKey set -> set -> Bool
- union :: set -> set -> set
- unions :: (MonoFoldable mono, Element mono ~ set) => mono -> set
- difference :: set -> set -> set
- intersection :: set -> set -> set
- keys :: set -> [ContainerKey set]
- class PolyMap map where
- differenceMap :: map value1 -> map value2 -> map value1
- intersectionMap :: map value1 -> map value2 -> map value1
- intersectionWithMap :: (value1 -> value2 -> value3) -> map value1 -> map value2 -> map value3
- class BiPolyMap map where
- type BPMKeyConstraint map key :: Constraint
- mapKeysWith :: (BPMKeyConstraint map k1, BPMKeyConstraint map k2) => (v -> v -> v) -> (k1 -> k2) -> map k1 v -> map k2 v
- class (MonoTraversable map, SetContainer map) => IsMap map where
- type MapValue map
- lookup :: ContainerKey map -> map -> Maybe (MapValue map)
- insertMap :: ContainerKey map -> MapValue map -> map -> map
- deleteMap :: ContainerKey map -> map -> map
- singletonMap :: ContainerKey map -> MapValue map -> map
- mapFromList :: [(ContainerKey map, MapValue map)] -> map
- mapToList :: map -> [(ContainerKey map, MapValue map)]
- findWithDefault :: MapValue map -> ContainerKey map -> map -> MapValue map
- insertWith :: (MapValue map -> MapValue map -> MapValue map) -> ContainerKey map -> MapValue map -> map -> map
- insertWithKey :: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) -> ContainerKey map -> MapValue map -> map -> map
- insertLookupWithKey :: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) -> ContainerKey map -> MapValue map -> map -> (Maybe (MapValue map), map)
- adjustMap :: (MapValue map -> MapValue map) -> ContainerKey map -> map -> map
- adjustWithKey :: (ContainerKey map -> MapValue map -> MapValue map) -> ContainerKey map -> map -> map
- updateMap :: (MapValue map -> Maybe (MapValue map)) -> ContainerKey map -> map -> map
- updateWithKey :: (ContainerKey map -> MapValue map -> Maybe (MapValue map)) -> ContainerKey map -> map -> map
- updateLookupWithKey :: (ContainerKey map -> MapValue map -> Maybe (MapValue map)) -> ContainerKey map -> map -> (Maybe (MapValue map), map)
- alterMap :: (Maybe (MapValue map) -> Maybe (MapValue map)) -> ContainerKey map -> map -> map
- unionWith :: (MapValue map -> MapValue map -> MapValue map) -> map -> map -> map
- unionWithKey :: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) -> map -> map -> map
- unionsWith :: (MapValue map -> MapValue map -> MapValue map) -> [map] -> map
- mapWithKey :: (ContainerKey map -> MapValue map -> MapValue map) -> map -> map
- omapKeysWith :: (MapValue map -> MapValue map -> MapValue map) -> (ContainerKey map -> ContainerKey map) -> map -> map
- filterMap :: IsMap map => (MapValue map -> Bool) -> map -> map
- class (SetContainer set, Element set ~ ContainerKey set) => IsSet set where
- class MonoFunctor mono => MonoZip mono where
- class SetContainer set => HasKeysSet set where
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.
Instances
SetContainer IntSet Source # | |
Defined in Data.Containers type ContainerKey IntSet :: Type Source # member :: ContainerKey IntSet -> IntSet -> Bool Source # notMember :: ContainerKey IntSet -> IntSet -> Bool Source # union :: IntSet -> IntSet -> IntSet Source # unions :: (MonoFoldable mono, Element mono ~ IntSet) => mono -> IntSet Source # difference :: IntSet -> IntSet -> IntSet Source # | |
Eq key => SetContainer [(key, value)] Source # | |
Defined in Data.Containers type ContainerKey [(key, value)] :: Type Source # member :: ContainerKey [(key, value)] -> [(key, value)] -> Bool Source # notMember :: ContainerKey [(key, value)] -> [(key, value)] -> Bool Source # union :: [(key, value)] -> [(key, value)] -> [(key, value)] Source # unions :: (MonoFoldable mono, Element mono ~ [(key, value)]) => mono -> [(key, value)] Source # difference :: [(key, value)] -> [(key, value)] -> [(key, value)] Source # intersection :: [(key, value)] -> [(key, value)] -> [(key, value)] Source # keys :: [(key, value)] -> [ContainerKey [(key, value)]] Source # | |
SetContainer (IntMap value) Source # | This instance uses the functions from Data.IntMap.Strict. |
Defined in Data.Containers type ContainerKey (IntMap value) :: Type Source # member :: ContainerKey (IntMap value) -> IntMap value -> Bool Source # notMember :: ContainerKey (IntMap value) -> IntMap value -> Bool Source # union :: IntMap value -> IntMap value -> IntMap value Source # unions :: (MonoFoldable mono, Element mono ~ IntMap value) => mono -> IntMap value Source # difference :: IntMap value -> IntMap value -> IntMap value Source # intersection :: IntMap value -> IntMap value -> IntMap value Source # keys :: IntMap value -> [ContainerKey (IntMap value)] Source # | |
Ord element => SetContainer (Set element) Source # | |
Defined in Data.Containers type ContainerKey (Set element) :: Type Source # member :: ContainerKey (Set element) -> Set element -> Bool Source # notMember :: ContainerKey (Set element) -> Set element -> Bool Source # union :: Set element -> Set element -> Set element Source # unions :: (MonoFoldable mono, Element mono ~ Set element) => mono -> Set element Source # difference :: Set element -> Set element -> Set element Source # intersection :: Set element -> Set element -> Set element Source # keys :: Set element -> [ContainerKey (Set element)] Source # | |
(Eq element, Hashable element) => SetContainer (HashSet element) Source # | |
Defined in Data.Containers type ContainerKey (HashSet element) :: Type Source # member :: ContainerKey (HashSet element) -> HashSet element -> Bool Source # notMember :: ContainerKey (HashSet element) -> HashSet element -> Bool Source # union :: HashSet element -> HashSet element -> HashSet element Source # unions :: (MonoFoldable mono, Element mono ~ HashSet element) => mono -> HashSet element Source # difference :: HashSet element -> HashSet element -> HashSet element Source # intersection :: HashSet element -> HashSet element -> HashSet element Source # keys :: HashSet element -> [ContainerKey (HashSet element)] Source # | |
Ord k => SetContainer (Map k v) Source # | This instance uses the functions from Data.Map.Strict. |
Defined in Data.Containers type ContainerKey (Map k v) :: Type Source # member :: ContainerKey (Map k v) -> Map k v -> Bool Source # notMember :: ContainerKey (Map k v) -> Map k v -> Bool Source # union :: Map k v -> Map k v -> Map k v Source # unions :: (MonoFoldable mono, Element mono ~ Map k v) => mono -> Map k v Source # difference :: Map k v -> Map k v -> Map k v Source # | |
(Eq key, Hashable key) => SetContainer (HashMap key value) Source # | This instance uses the functions from Data.HashMap.Strict. |
Defined in Data.Containers type ContainerKey (HashMap key value) :: Type Source # member :: ContainerKey (HashMap key value) -> HashMap key value -> Bool Source # notMember :: ContainerKey (HashMap key value) -> HashMap key value -> Bool Source # union :: HashMap key value -> HashMap key value -> HashMap key value Source # unions :: (MonoFoldable mono, Element mono ~ HashMap key value) => mono -> HashMap key value Source # difference :: HashMap key value -> HashMap key value -> HashMap key value Source # intersection :: HashMap key value -> HashMap key value -> HashMap key value Source # keys :: HashMap key value -> [ContainerKey (HashMap key value)] Source # |
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.
Instances
PolyMap IntMap Source # | This instance uses the functions from Data.IntMap.Strict. |
Defined in Data.Containers | |
Ord key => PolyMap (Map key) Source # | This instance uses the functions from Data.Map.Strict. |
Defined in Data.Containers | |
(Eq key, Hashable key) => PolyMap (HashMap key) Source # | This instance uses the functions from Data.HashMap.Strict. |
Defined in Data.Containers differenceMap :: HashMap key value1 -> HashMap key value2 -> HashMap key value1 Source # intersectionMap :: HashMap key value1 -> HashMap key value2 -> HashMap key value1 Source # intersectionWithMap :: (value1 -> value2 -> value3) -> HashMap key value1 -> HashMap key value2 -> HashMap key value3 Source # |
class BiPolyMap map where Source #
A Map
type polymorphic in both its key and value.
type BPMKeyConstraint map key :: Constraint Source #
:: (BPMKeyConstraint map k1, BPMKeyConstraint map k2) | |
=> (v -> v -> v) | combine values that now overlap |
-> (k1 -> k2) | |
-> map k1 v | |
-> map k2 v |
Instances
BiPolyMap Map Source # | |
Defined in Data.Containers 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 # | |
BiPolyMap HashMap Source # | |
Defined in Data.Containers type BPMKeyConstraint HashMap key :: Constraint Source # mapKeysWith :: (BPMKeyConstraint HashMap k1, BPMKeyConstraint HashMap k2) => (v -> v -> v) -> (k1 -> k2) -> HashMap k1 v -> HashMap 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.
:: (MapValue map -> MapValue map -> MapValue map) | function that accepts the new value and the previous value and returns the value that will be set in the map. |
-> ContainerKey map | key |
-> MapValue map | new value to insert |
-> map | input map |
-> map | resulting map |
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.
:: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) | function that accepts the key, the new value, and the previous value and returns the value that will be set in the map. |
-> ContainerKey map | key |
-> MapValue map | new value to insert |
-> map | input map |
-> map | resulting map |
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.
:: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) | function that accepts the key, the new value, and the previous value and returns the value that will be set in the map. |
-> ContainerKey map | key |
-> MapValue map | new value to insert |
-> map | input map |
-> (Maybe (MapValue map), map) | previous value and the resulting map |
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.
:: (MapValue map -> MapValue map) | function to apply to the previous value |
-> ContainerKey map | key |
-> map | input map |
-> map | resulting map |
Apply a function to the value of a given key.
Returns the input map when the key-value pair does not exist.
:: (ContainerKey map -> MapValue map -> MapValue map) | function that accepts the key and the previous value and returns the new value |
-> ContainerKey map | key |
-> map | input map |
-> map | resulting map |
Equivalent to adjustMap
, but the function accepts the key,
as well as the previous value.
:: (MapValue map -> Maybe (MapValue map)) | function that accepts the previous value
and returns the new value or |
-> ContainerKey map | key |
-> map | input map |
-> map | resulting map |
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.
:: (ContainerKey map -> MapValue map -> Maybe (MapValue map)) | function that accepts the key and the previous value
and returns the new value or |
-> ContainerKey map | key |
-> map | input map |
-> map | resulting map |
Equivalent to updateMap
, but the function accepts the key,
as well as the previous value.
:: (ContainerKey map -> MapValue map -> Maybe (MapValue map)) | function that accepts the key and the previous value
and returns the new value or |
-> ContainerKey map | key |
-> map | input map |
-> (Maybe (MapValue map), map) | previous/new value and the resulting map |
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.
:: (Maybe (MapValue map) -> Maybe (MapValue map)) | function that accepts the previous value and
returns the new value or |
-> ContainerKey map | key |
-> map | input map |
-> map | resulting map |
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.
:: (MapValue map -> MapValue map -> MapValue map) | function that accepts the first map's value and the second map's value and returns the new value that will be used |
-> map | first map |
-> map | second map |
-> map | resulting map |
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.
:: (ContainerKey map -> MapValue map -> MapValue map -> MapValue map) | function that accepts the key, the first map's value and the second map's value and returns the new value that will be used |
-> map | first map |
-> map | second map |
-> map | resulting map |
:: (MapValue map -> MapValue map -> MapValue map) | function that accepts the first map's value and the second map's value and returns the new value that will be used |
-> [map] | input list of maps |
-> map | resulting map |
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.
:: (ContainerKey map -> MapValue map -> MapValue map) | function that accepts the key and the previous value and returns the new value |
-> map | input map |
-> map | resulting map |
Apply a function over every key-value pair of a map.
:: (MapValue map -> MapValue map -> MapValue map) | function that accepts the first map's value and the second map's value and returns the new value that will be used |
-> (ContainerKey map -> ContainerKey map) | function that accepts the previous key and returns the new key |
-> map | input map |
-> map | resulting map |
Apply a function over every key of a pair and run
unionsWith
over the results.
filterMap :: IsMap map => (MapValue map -> Bool) -> map -> map Source #
Filter values in a map.
Since: 1.0.9.0
Instances
Eq key => IsMap [(key, value)] Source # | |
Defined in Data.Containers lookup :: ContainerKey [(key, value)] -> [(key, value)] -> Maybe (MapValue [(key, value)]) Source # insertMap :: ContainerKey [(key, value)] -> MapValue [(key, value)] -> [(key, value)] -> [(key, value)] Source # deleteMap :: ContainerKey [(key, value)] -> [(key, value)] -> [(key, value)] Source # singletonMap :: ContainerKey [(key, value)] -> MapValue [(key, value)] -> [(key, value)] Source # mapFromList :: [(ContainerKey [(key, value)], MapValue [(key, value)])] -> [(key, value)] Source # mapToList :: [(key, value)] -> [(ContainerKey [(key, value)], MapValue [(key, value)])] Source # findWithDefault :: MapValue [(key, value)] -> ContainerKey [(key, value)] -> [(key, value)] -> MapValue [(key, value)] Source # insertWith :: (MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> ContainerKey [(key, value)] -> MapValue [(key, value)] -> [(key, value)] -> [(key, value)] Source # insertWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> ContainerKey [(key, value)] -> MapValue [(key, value)] -> [(key, value)] -> [(key, value)] Source # insertLookupWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> ContainerKey [(key, value)] -> MapValue [(key, value)] -> [(key, value)] -> (Maybe (MapValue [(key, value)]), [(key, value)]) Source # adjustMap :: (MapValue [(key, value)] -> MapValue [(key, value)]) -> ContainerKey [(key, value)] -> [(key, value)] -> [(key, value)] Source # adjustWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> ContainerKey [(key, value)] -> [(key, value)] -> [(key, value)] Source # updateMap :: (MapValue [(key, value)] -> Maybe (MapValue [(key, value)])) -> ContainerKey [(key, value)] -> [(key, value)] -> [(key, value)] Source # updateWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> Maybe (MapValue [(key, value)])) -> ContainerKey [(key, value)] -> [(key, value)] -> [(key, value)] Source # updateLookupWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> Maybe (MapValue [(key, value)])) -> ContainerKey [(key, value)] -> [(key, value)] -> (Maybe (MapValue [(key, value)]), [(key, value)]) Source # alterMap :: (Maybe (MapValue [(key, value)]) -> Maybe (MapValue [(key, value)])) -> ContainerKey [(key, value)] -> [(key, value)] -> [(key, value)] Source # unionWith :: (MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> [(key, value)] -> [(key, value)] -> [(key, value)] Source # unionWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> [(key, value)] -> [(key, value)] -> [(key, value)] Source # unionsWith :: (MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> [[(key, value)]] -> [(key, value)] Source # mapWithKey :: (ContainerKey [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> [(key, value)] -> [(key, value)] Source # omapKeysWith :: (MapValue [(key, value)] -> MapValue [(key, value)] -> MapValue [(key, value)]) -> (ContainerKey [(key, value)] -> ContainerKey [(key, value)]) -> [(key, value)] -> [(key, value)] Source # filterMap :: (MapValue [(key, value)] -> Bool) -> [(key, value)] -> [(key, value)] Source # | |
IsMap (IntMap value) Source # | This instance uses the functions from Data.IntMap.Strict. |
Defined in Data.Containers lookup :: ContainerKey (IntMap value) -> IntMap value -> Maybe (MapValue (IntMap value)) Source # insertMap :: ContainerKey (IntMap value) -> MapValue (IntMap value) -> IntMap value -> IntMap value Source # deleteMap :: ContainerKey (IntMap value) -> IntMap value -> IntMap value Source # singletonMap :: ContainerKey (IntMap value) -> MapValue (IntMap value) -> IntMap value Source # mapFromList :: [(ContainerKey (IntMap value), MapValue (IntMap value))] -> IntMap value Source # mapToList :: IntMap value -> [(ContainerKey (IntMap value), MapValue (IntMap value))] Source # findWithDefault :: MapValue (IntMap value) -> ContainerKey (IntMap value) -> IntMap value -> MapValue (IntMap value) Source # insertWith :: (MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> ContainerKey (IntMap value) -> MapValue (IntMap value) -> IntMap value -> IntMap value Source # insertWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> ContainerKey (IntMap value) -> MapValue (IntMap value) -> IntMap value -> IntMap value Source # insertLookupWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> ContainerKey (IntMap value) -> MapValue (IntMap value) -> IntMap value -> (Maybe (MapValue (IntMap value)), IntMap value) Source # adjustMap :: (MapValue (IntMap value) -> MapValue (IntMap value)) -> ContainerKey (IntMap value) -> IntMap value -> IntMap value Source # adjustWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> ContainerKey (IntMap value) -> IntMap value -> IntMap value Source # updateMap :: (MapValue (IntMap value) -> Maybe (MapValue (IntMap value))) -> ContainerKey (IntMap value) -> IntMap value -> IntMap value Source # updateWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> Maybe (MapValue (IntMap value))) -> ContainerKey (IntMap value) -> IntMap value -> IntMap value Source # updateLookupWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> Maybe (MapValue (IntMap value))) -> ContainerKey (IntMap value) -> IntMap value -> (Maybe (MapValue (IntMap value)), IntMap value) Source # alterMap :: (Maybe (MapValue (IntMap value)) -> Maybe (MapValue (IntMap value))) -> ContainerKey (IntMap value) -> IntMap value -> IntMap value Source # unionWith :: (MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> IntMap value -> IntMap value -> IntMap value Source # unionWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> IntMap value -> IntMap value -> IntMap value Source # unionsWith :: (MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> [IntMap value] -> IntMap value Source # mapWithKey :: (ContainerKey (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> IntMap value -> IntMap value Source # omapKeysWith :: (MapValue (IntMap value) -> MapValue (IntMap value) -> MapValue (IntMap value)) -> (ContainerKey (IntMap value) -> ContainerKey (IntMap value)) -> IntMap value -> IntMap value Source # filterMap :: (MapValue (IntMap value) -> Bool) -> IntMap value -> IntMap value Source # | |
Ord key => IsMap (Map key value) Source # | This instance uses the functions from Data.Map.Strict. |
Defined in Data.Containers lookup :: ContainerKey (Map key value) -> Map key value -> Maybe (MapValue (Map key value)) Source # insertMap :: ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value Source # deleteMap :: ContainerKey (Map key value) -> Map key value -> Map key value Source # singletonMap :: ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value Source # mapFromList :: [(ContainerKey (Map key value), MapValue (Map key value))] -> Map key value Source # mapToList :: Map key value -> [(ContainerKey (Map key value), MapValue (Map key value))] Source # findWithDefault :: MapValue (Map key value) -> ContainerKey (Map key value) -> Map key value -> MapValue (Map key value) Source # insertWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value Source # insertWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value Source # insertLookupWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> (Maybe (MapValue (Map key value)), Map key value) Source # adjustMap :: (MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> Map key value -> Map key value Source # adjustWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> Map key value -> Map key value Source # updateMap :: (MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value Source # updateWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value Source # updateLookupWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> (Maybe (MapValue (Map key value)), Map key value) Source # alterMap :: (Maybe (MapValue (Map key value)) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value Source # unionWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value -> Map key value Source # unionWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value -> Map key value Source # unionsWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> [Map key value] -> Map key value Source # mapWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value Source # omapKeysWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> (ContainerKey (Map key value) -> ContainerKey (Map key value)) -> Map key value -> Map key value Source # filterMap :: (MapValue (Map key value) -> Bool) -> Map key value -> Map key value Source # | |
(Eq key, Hashable key) => IsMap (HashMap key value) Source # | This instance uses the functions from Data.HashMap.Strict. |
Defined in Data.Containers lookup :: ContainerKey (HashMap key value) -> HashMap key value -> Maybe (MapValue (HashMap key value)) Source # insertMap :: ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> HashMap key value Source # deleteMap :: ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value Source # singletonMap :: ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value Source # mapFromList :: [(ContainerKey (HashMap key value), MapValue (HashMap key value))] -> HashMap key value Source # mapToList :: HashMap key value -> [(ContainerKey (HashMap key value), MapValue (HashMap key value))] Source # findWithDefault :: MapValue (HashMap key value) -> ContainerKey (HashMap key value) -> HashMap key value -> MapValue (HashMap key value) Source # insertWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> HashMap key value Source # insertWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> HashMap key value Source # insertLookupWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> (Maybe (MapValue (HashMap key value)), HashMap key value) Source # adjustMap :: (MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value Source # adjustWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value Source # updateMap :: (MapValue (HashMap key value) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value Source # updateWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value Source # updateLookupWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> (Maybe (MapValue (HashMap key value)), HashMap key value) Source # alterMap :: (Maybe (MapValue (HashMap key value)) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value Source # unionWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> HashMap key value -> HashMap key value -> HashMap key value Source # unionWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> HashMap key value -> HashMap key value -> HashMap key value Source # unionsWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> [HashMap key value] -> HashMap key value Source # mapWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> HashMap key value -> HashMap key value Source # omapKeysWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> (ContainerKey (HashMap key value) -> ContainerKey (HashMap key value)) -> HashMap key value -> HashMap key value Source # filterMap :: (MapValue (HashMap key value) -> Bool) -> HashMap key value -> HashMap key value Source # |
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.
filterSet :: (Element set -> Bool) -> set -> set Source #
Filter values in a set.
Since: 1.0.12.0
Instances
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 #
Instances
MonoZip ByteString Source # | |
Defined in Data.Containers ozipWith :: (Element ByteString -> Element ByteString -> Element ByteString) -> ByteString -> ByteString -> ByteString Source # ozip :: ByteString -> ByteString -> [(Element ByteString, Element ByteString)] Source # ounzip :: [(Element ByteString, Element ByteString)] -> (ByteString, ByteString) Source # | |
MonoZip ByteString Source # | |
Defined in Data.Containers ozipWith :: (Element ByteString -> Element ByteString -> Element ByteString) -> ByteString -> ByteString -> ByteString Source # ozip :: ByteString -> ByteString -> [(Element ByteString, Element ByteString)] Source # ounzip :: [(Element ByteString, Element ByteString)] -> (ByteString, ByteString) Source # | |
MonoZip Text Source # | |
MonoZip Text Source # | |
class SetContainer set => HasKeysSet set where Source #
Type class for maps whose keys can be converted into sets.
Instances
HasKeysSet (IntMap v) Source # | |
Ord k => HasKeysSet (Map k v) Source # | |
(Hashable k, Eq k) => HasKeysSet (HashMap k v) Source # | |