mono-traversable-1.0.1.1: Type classes for mapping, folding, and traversing monomorphic containers

Safe HaskellNone
LanguageHaskell2010

Data.Containers

Description

Warning: This module should be considered highly experimental.

Synopsis

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.

Minimal complete definition

member, notMember, union, difference, intersection, keys

Associated Types

type ContainerKey set Source #

The type of the key

Methods

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 SetContainers, 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 # 
Eq key => SetContainer [(key, value)] Source # 

Associated Types

type ContainerKey [(key, value)] :: * Source #

Methods

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.

Associated Types

type ContainerKey (IntMap value) :: * Source #

Methods

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 # 

Associated Types

type ContainerKey (Set element) :: * Source #

Methods

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 # 

Associated Types

type ContainerKey (HashSet element) :: * Source #

Methods

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.

Associated Types

type ContainerKey (Map k v) :: * Source #

Methods

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 #

intersection :: Map k v -> Map k v -> Map k v Source #

keys :: Map k v -> [ContainerKey (Map k v)] Source #

(Eq key, Hashable key) => SetContainer (HashMap key value) Source #

This instance uses the functions from Data.HashMap.Strict.

Associated Types

type ContainerKey (HashMap key value) :: * Source #

Methods

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.

Methods

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.

Methods

differenceMap :: IntMap value1 -> IntMap value2 -> IntMap value1 Source #

intersectionMap :: IntMap value1 -> IntMap value2 -> IntMap value1 Source #

intersectionWithMap :: (value1 -> value2 -> value3) -> IntMap value1 -> IntMap value2 -> IntMap value3 Source #

Ord key => PolyMap (Map key) Source #

This instance uses the functions from Data.Map.Strict.

Methods

differenceMap :: Map key value1 -> Map key value2 -> Map key value1 Source #

intersectionMap :: Map key value1 -> Map key value2 -> Map key value1 Source #

intersectionWithMap :: (value1 -> value2 -> value3) -> Map key value1 -> Map key value2 -> Map key value3 Source #

(Eq key, Hashable key) => PolyMap (HashMap key) Source #

This instance uses the functions from Data.HashMap.Strict.

Methods

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.

Minimal complete definition

mapKeysWith

Associated Types

type BPMKeyConstraint map key :: Constraint Source #

Methods

mapKeysWith :: (BPMKeyConstraint map k1, BPMKeyConstraint map k2) => (v -> v -> v) -> (k1 -> k2) -> map k1 v -> map k2 v Source #

Instances

BiPolyMap Map Source # 

Associated Types

type BPMKeyConstraint (Map :: * -> * -> *) key :: Constraint Source #

Methods

mapKeysWith :: (BPMKeyConstraint Map k1, BPMKeyConstraint Map k2) => (v -> v -> v) -> (k1 -> k2) -> Map k1 v -> Map k2 v Source #

BiPolyMap HashMap Source # 

Associated Types

type BPMKeyConstraint (HashMap :: * -> * -> *) key :: Constraint Source #

Methods

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

Associated Types

type MapValue map Source #

In some cases, MapValue and Element will be different, e.g., the IsMap instance of associated lists.

Methods

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.

Instances

Eq key => IsMap [(key, value)] Source # 

Associated Types

type MapValue [(key, value)] :: * Source #

Methods

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 #

IsMap (IntMap value) Source #

This instance uses the functions from Data.IntMap.Strict.

Associated Types

type MapValue (IntMap value) :: * Source #

Methods

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 #

Ord key => IsMap (Map key value) Source #

This instance uses the functions from Data.Map.Strict.

Associated Types

type MapValue (Map key value) :: * Source #

Methods

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 #

(Eq key, Hashable key) => IsMap (HashMap key value) Source #

This instance uses the functions from Data.HashMap.Strict.

Associated Types

type MapValue (HashMap key value) :: * Source #

Methods

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 #

class (SetContainer set, Element set ~ ContainerKey set) => IsSet set where Source #

Polymorphic typeclass for interacting with different set types

Minimal complete definition

insertSet, deleteSet, singletonSet, setFromList, setToList

Methods

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.

Instances

IsSet IntSet Source # 
Ord element => IsSet (Set element) Source # 

Methods

insertSet :: Element (Set element) -> Set element -> Set element Source #

deleteSet :: Element (Set element) -> Set element -> Set element Source #

singletonSet :: Element (Set element) -> Set element Source #

setFromList :: [Element (Set element)] -> Set element Source #

setToList :: Set element -> [Element (Set element)] Source #

(Eq element, Hashable element) => IsSet (HashSet element) Source # 

Methods

insertSet :: Element (HashSet element) -> HashSet element -> HashSet element Source #

deleteSet :: Element (HashSet element) -> HashSet element -> HashSet element Source #

singletonSet :: Element (HashSet element) -> HashSet element Source #

setFromList :: [Element (HashSet element)] -> HashSet element Source #

setToList :: HashSet element -> [Element (HashSet element)] Source #

class MonoFunctor mono => MonoZip mono where Source #

Zip operations on MonoFunctors.

Minimal complete definition

ozipWith, ozip, ounzip

Methods

ozipWith :: (Element mono -> Element mono -> Element mono) -> mono -> mono -> mono Source #

Combine each element of two MonoZips using a supplied function.

ozip :: mono -> mono -> [(Element mono, Element mono)] Source #

Take two MonoZips and return a list of the pairs of their elements.

ounzip :: [(Element mono, Element mono)] -> (mono, mono) Source #

Take a list of pairs of elements and return a MonoZip of the first components and a MonoZip of the second components.

class SetContainer set => HasKeysSet set where Source #

Type class for maps whose keys can be converted into sets.

Minimal complete definition

keysSet

Associated Types

type KeySet set Source #

Type of the key set.

Methods

keysSet :: set -> KeySet set Source #

Convert a map into a set of its keys.

Instances

HasKeysSet (IntMap v) Source # 

Associated Types

type KeySet (IntMap v) :: * Source #

Methods

keysSet :: IntMap v -> KeySet (IntMap v) Source #

Ord k => HasKeysSet (Map k v) Source # 

Associated Types

type KeySet (Map k v) :: * Source #

Methods

keysSet :: Map k v -> KeySet (Map k v) Source #

(Hashable k, Eq k) => HasKeysSet (HashMap k v) Source # 

Associated Types

type KeySet (HashMap k v) :: * Source #

Methods

keysSet :: HashMap k v -> KeySet (HashMap k v) Source #