mono-traversable-0.9.2: 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.

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.

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

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

Ord element => SetContainer (Set element) 
(Eq element, Hashable element) => SetContainer (HashSet element) 
Ord k => SetContainer (Map k v)

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

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

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.

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

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

Ord key => PolyMap (Map key)

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

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

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

class BiPolyMap map where Source

A Map type polymorphic in both its key and value.

Associated Types

type BPMKeyConstraint map key :: Constraint Source

Methods

mapKeysWith Source

Arguments

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

combine values that now overlap

-> (k1 -> k2) 
-> map k1 v 
-> map k2 v 

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 Source

Arguments

:: (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.

insertWithKey Source

Arguments

:: (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.

insertLookupWithKey Source

Arguments

:: (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.

adjustMap Source

Arguments

:: (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.

adjustWithKey Source

Arguments

:: (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.

updateMap Source

Arguments

:: (MapValue map -> Maybe (MapValue map))

function that accepts the previous value and returns the new value or Nothing

-> 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.

updateWithKey Source

Arguments

:: (ContainerKey map -> MapValue map -> Maybe (MapValue map))

function that accepts the key and the previous value and returns the new value or Nothing

-> ContainerKey map

key

-> map

input map

-> map

resulting map

Equivalent to updateMap, but the function accepts the key, as well as the previous value.

updateLookupWithKey Source

Arguments

:: (ContainerKey map -> MapValue map -> Maybe (MapValue map))

function that accepts the key and the previous value and returns the new value or Nothing

-> 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.

alterMap Source

Arguments

:: (Maybe (MapValue map) -> Maybe (MapValue map))

function that accepts the previous value and returns the new value or Nothing

-> 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.

unionWith Source

Arguments

:: (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.

unionWithKey Source

Arguments

:: (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

unionsWith Source

Arguments

:: (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.

mapWithKey Source

Arguments

:: (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.

omapKeysWith Source

Arguments

:: (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.

Instances

Eq key => IsMap [(key, value)] 
IsMap (IntMap value)

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

Ord key => IsMap (Map key value)

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

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

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

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 
Ord element => IsSet (Set element) 
(Eq element, Hashable element) => IsSet (HashSet element) 

class MonoFunctor mono => MonoZip mono where Source

Zip operations on MonoFunctors.

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.

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) 
Ord k => HasKeysSet (Map k v) 
(Hashable k, Eq k) => HasKeysSet (HashMap k v)