Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module implements an interface for working with maps.
For primitive types, like Int
, the library automatically selects
an efficient implementation (e.g., an IntMap).
For complex structured types, the library uses an implementation based on tries: this is useful when using large and similar keys where comparing for order may become expensive, and storing the distinct keys would be inefficient.
The OrdKey
type allows for maps with complex keys,
where the keys are compared based on order, rather than using the
trie implementation.
All methods of TrieKey
can be derived automatically using
a Generic
instance.
data Demo = DemoC1Int
| DemoC2Int
Char
derivingGeneric
instanceTrieKey
Demo
- data Trie k a
- class TrieKey k
- empty :: TrieKey k => Trie k a
- singleton :: TrieKey k => k -> a -> Trie k a
- fromList :: TrieKey k => [(k, v)] -> Trie k v
- fromListWith :: TrieKey k => (v -> v -> v) -> [(k, v)] -> Trie k v
- fromListWith' :: TrieKey k => (v -> v -> v) -> [(k, v)] -> Trie k v
- alter :: TrieKey k => k -> (Maybe a -> Maybe a) -> Trie k a -> Trie k a
- insert :: TrieKey k => k -> a -> Trie k a -> Trie k a
- insertWith :: TrieKey k => (v -> v -> v) -> k -> v -> Trie k v -> Trie k v
- insertWith' :: TrieKey k => (v -> v -> v) -> k -> v -> Trie k v -> Trie k v
- delete :: TrieKey k => k -> Trie k a -> Trie k a
- at :: (Functor f, TrieKey k) => k -> (Maybe a -> f (Maybe a)) -> Trie k a -> f (Trie k a)
- member :: TrieKey k => k -> Trie k a -> Bool
- notMember :: TrieKey k => k -> Trie k a -> Bool
- null :: TrieKey k => Trie k a -> Bool
- lookup :: TrieKey k => k -> Trie k a -> Maybe a
- foldWithKey :: TrieKey k => (k -> a -> r -> r) -> r -> Trie k a -> r
- fold :: TrieKey k => (a -> r -> r) -> r -> Trie k a -> r
- toList :: TrieKey k => Trie k a -> [(k, a)]
- traverseWithKey :: (TrieKey k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b)
- mapMaybe :: TrieKey k => (a -> Maybe b) -> Trie k a -> Trie k b
- mapMaybeWithKey :: TrieKey k => (k -> a -> Maybe b) -> Trie k a -> Trie k b
- filter :: TrieKey k => (a -> Bool) -> Trie k a -> Trie k a
- filterWithKey :: TrieKey k => (k -> a -> Bool) -> Trie k a -> Trie k a
- union :: TrieKey k => Trie k a -> Trie k a -> Trie k a
- unionWith :: TrieKey k => (a -> a -> a) -> Trie k a -> Trie k a -> Trie k a
- unionWithKey :: TrieKey k => (k -> a -> a -> a) -> Trie k a -> Trie k a -> Trie k a
- intersection :: TrieKey k => Trie k a -> Trie k b -> Trie k a
- intersectionWith :: TrieKey k => (a -> b -> c) -> Trie k a -> Trie k b -> Trie k c
- intersectionWithKey :: TrieKey k => (k -> a -> b -> c) -> Trie k a -> Trie k b -> Trie k c
- difference :: TrieKey k => Trie k a -> Trie k b -> Trie k a
- differenceWith :: TrieKey k => (a -> b -> Maybe a) -> Trie k a -> Trie k b -> Trie k a
- differenceWithKey :: TrieKey k => (k -> a -> b -> Maybe a) -> Trie k a -> Trie k b -> Trie k a
- newtype OrdKey k = OrdKey {
- getOrdKey :: k
Trie interface
A map from keys of type k
, to values of type a
.
Types that may be used as the key of a Trie
.
For data
declarations, the instance can be automatically derived from
a Generic
instance.
TrieKey Bool Source # | |
TrieKey Char Source # | |
TrieKey Int Source # | |
TrieKey Integer Source # | |
TrieKey () Source # | |
TrieKey k => TrieKey [k] Source # | |
TrieKey k => TrieKey (Maybe k) Source # | |
(Show k, Ord k) => TrieKey (OrdKey k) Source # |
|
(TrieKey a, TrieKey b) => TrieKey (Either a b) Source # | |
(TrieKey a, TrieKey b) => TrieKey (a, b) Source # | |
(TrieKey a, TrieKey b, TrieKey c) => TrieKey (a, b, c) Source # | |
(TrieKey a, TrieKey b, TrieKey c, TrieKey d) => TrieKey (a, b, c, d) Source # | |
(TrieKey a, TrieKey b, TrieKey c, TrieKey d, TrieKey e) => TrieKey (a, b, c, d, e) Source # | |
Construction
fromList :: TrieKey k => [(k, v)] -> Trie k v Source #
Construct a trie from a list of key-value pairs
fromListWith :: TrieKey k => (v -> v -> v) -> [(k, v)] -> Trie k v Source #
Construct a trie from a list of key-value pairs. The given function is used to combine values at the same key.
fromListWith' :: TrieKey k => (v -> v -> v) -> [(k, v)] -> Trie k v Source #
Version of fromListWith
which is strict in the result of
the combining function.
Updates
alter :: TrieKey k => k -> (Maybe a -> Maybe a) -> Trie k a -> Trie k a Source #
Alter the value at the given key location.
The parameter function takes the value stored
at the given key, if one exists, and should return a value to insert at
that location, or Nothing
to delete from that location.
insertWith :: TrieKey k => (v -> v -> v) -> k -> v -> Trie k v -> Trie k v Source #
Insert a value at the given key. The combining function is used when a value is already stored at that key. The new value is the first argument to the combining function.
insertWith' :: TrieKey k => (v -> v -> v) -> k -> v -> Trie k v -> Trie k v Source #
Version of insertWith
that is strict in the result of combining
two elements.
at :: (Functor f, TrieKey k) => k -> (Maybe a -> f (Maybe a)) -> Trie k a -> f (Trie k a) Source #
Lens for the value at a given key
Queries
Folding
foldWithKey :: TrieKey k => (k -> a -> r -> r) -> r -> Trie k a -> r Source #
Fold a trie with a function of both key and value
fold :: TrieKey k => (a -> r -> r) -> r -> Trie k a -> r Source #
Fold a trie with a function of the value
Traversing
traverseWithKey :: (TrieKey k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b) Source #
Traverse a trie with a function of both key and value
mapMaybe :: TrieKey k => (a -> Maybe b) -> Trie k a -> Trie k b Source #
Map a function over a trie filtering out elements where function returns Nothing
mapMaybeWithKey :: TrieKey k => (k -> a -> Maybe b) -> Trie k a -> Trie k b Source #
Apply a function to the values of a trie and keep the elements
of the trie that result in a Just
value.
filter :: TrieKey k => (a -> Bool) -> Trie k a -> Trie k a Source #
Filter the values of a trie with the given predicate.
filterWithKey :: TrieKey k => (k -> a -> Bool) -> Trie k a -> Trie k a Source #
Version of filter
where the predicate also gets the key.
Combining maps
unionWith :: TrieKey k => (a -> a -> a) -> Trie k a -> Trie k a -> Trie k a Source #
Union of two tries with function used to merge overlapping elements
unionWithKey :: TrieKey k => (k -> a -> a -> a) -> Trie k a -> Trie k a -> Trie k a Source #
Union of two tries with function used to merge overlapping elements along with key
intersection :: TrieKey k => Trie k a -> Trie k b -> Trie k a Source #
Left-biased intersection of two tries
intersectionWith :: TrieKey k => (a -> b -> c) -> Trie k a -> Trie k b -> Trie k c Source #
Intersection of two tries parameterized by a combining function of the values at overlapping keys
intersectionWithKey :: TrieKey k => (k -> a -> b -> c) -> Trie k a -> Trie k b -> Trie k c Source #
Intersection of two tries parameterized by a combining function of the key and the values at overlapping keys
difference :: TrieKey k => Trie k a -> Trie k b -> Trie k a Source #
Remove the keys of the right trie from the left trie
differenceWith :: TrieKey k => (a -> b -> Maybe a) -> Trie k a -> Trie k b -> Trie k a Source #
Parameterized difference
using a custom merge function.
Return Just
to change the value stored in left trie, or
Nothing
to remove from the left trie.
differenceWithKey :: TrieKey k => (k -> a -> b -> Maybe a) -> Trie k a -> Trie k b -> Trie k a Source #
differenceWith
where function also has access to the key
Keys using Ord
Tries indexed by OrdKey
will be represented as an ordinary Map
and the keys will be compared based on the Ord
instance for k
.
Eq k => Eq (OrdKey k) Source # | |
Ord k => Ord (OrdKey k) Source # | |
Read k => Read (OrdKey k) Source # | |
Show k => Show (OrdKey k) Source # | |
(Show k, Ord k) => TrieKey (OrdKey k) Source # |
|
type TrieRep (OrdKey k) Source # | |