Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Convenience wrappers around dictionary and collection types and tools facilitating conversion between them and various map and set types in common use in the Haskell ecosystem.
Synopsis
- data Map κ ν
- emptyMap :: Map κ ν
- singletonMap :: Key κ => κ -> ν -> Map κ ν
- insertKeyValue :: Key κ => κ -> ν -> Map κ ν -> Map κ ν
- containsKey :: Key κ => κ -> Map κ ν -> Bool
- lookupKeyValue :: Key κ => κ -> Map κ ν -> Maybe ν
- removeKeyValue :: Key κ => κ -> Map κ ν -> Map κ ν
- class Dictionary α where
- data Set ε
- emptySet :: Key ε => Set ε
- singletonSet :: Key ε => ε -> Set ε
- insertElement :: Key ε => ε -> Set ε -> Set ε
- containsElement :: Key ε => ε -> Set ε -> Bool
- removeElement :: Key ε => ε -> Set ε -> Set ε
- class Collection α where
- class (Hashable κ, Ord κ) => Key κ
- unMap :: Map κ ν -> HashMap κ ν
- unSet :: Set ε -> HashSet ε
Map type
A mapping from keys to values.
The keys in a map needs to be an instance of the Key
typeclass.
Instances are already provided for many common element types.
Map
implements Foldable
, Monoid
, etc so many common operations such
as foldr
to reduce the structure with a right fold, length
to get the
number of key/value pairs in the dictionary, null
to test whether the
map is empty, and (<>
) to join two maps together are available.
To convert to other dictionary types see fromMap
below.
(this is a thin wrapper around unordered-containers's
HashMap
, but if you use the conversion functions to
extract the key/value pairs in a list the list will be ordered according to
the keys' Ord
instance)
Instances
Bifoldable Map Source # | |
Foldable (Map κ) Source # | |
Defined in Core.Data.Structures fold :: Monoid m => Map κ m -> m # foldMap :: Monoid m => (a -> m) -> Map κ a -> m # foldMap' :: Monoid m => (a -> m) -> Map κ a -> m # foldr :: (a -> b -> b) -> b -> Map κ a -> b # foldr' :: (a -> b -> b) -> b -> Map κ a -> b # foldl :: (b -> a -> b) -> b -> Map κ a -> b # foldl' :: (b -> a -> b) -> b -> Map κ a -> b # foldr1 :: (a -> a -> a) -> Map κ a -> a # foldl1 :: (a -> a -> a) -> Map κ a -> a # elem :: Eq a => a -> Map κ a -> Bool # maximum :: Ord a => Map κ a -> a # minimum :: Ord a => Map κ a -> a # | |
Key κ => Monoid (Map κ ν) Source # | |
Key κ => Semigroup (Map κ ν) Source # | |
Key κ => IsList (Map κ ν) Source # | |
(Show κ, Show ν) => Show (Map κ ν) Source # | |
Key κ => Dictionary (Map κ ν) Source # | |
(Eq κ, Eq ν) => Eq (Map κ ν) Source # | |
type Item (Map κ ν) Source # | |
Defined in Core.Data.Structures | |
type K (Map κ ν) Source # | |
Defined in Core.Data.Structures | |
type V (Map κ ν) Source # | |
Defined in Core.Data.Structures |
singletonMap :: Key κ => κ -> ν -> Map κ ν Source #
Construct a dictionary with only a single key/value pair.
insertKeyValue :: Key κ => κ -> ν -> Map κ ν -> Map κ ν Source #
Insert a key/value pair into the dictionary. If the key is already present in the dictionary, the old value will be discarded and replaced with the value supplied here.
lookupKeyValue :: Key κ => κ -> Map κ ν -> Maybe ν Source #
If the dictionary contains the specified key, return the value associated with that key.
removeKeyValue :: Key κ => κ -> Map κ ν -> Map κ ν Source #
Remove a key/value pair if present in the dictionary.
Since: 0.3.7
Conversions
class Dictionary α where Source #
Types that represent key/value pairs that can be converted to Map
s.
Haskell's ecosystem has several such. This typeclass provides an adaptor to
get between them. It also allows you to serialize out to an association
list.
For example, to convert a Map
to an "association list" of key/value
pairs, use fromMap
:
answers ::Map
Rope
Int
answers =singletonMap
"Life, The Universe, and Everything" 42 list :: [(Rope
,Int
)] list =fromMap
answers
Instances are provided for containers's Map
and
unordered-containers's HashMap
in addition to the
instance for [(κ,ν)]
lists shown above.
Instances
Key κ => Dictionary [(κ, ν)] Source # | |
Key κ => Dictionary (Map κ ν) Source # | from Data.Map.Strict (and .Lazy) |
Key κ => Dictionary (Map κ ν) Source # | |
Key κ => Dictionary (HashMap κ ν) Source # | from Data.HashMap.Strict (and .Lazy) |
Set type
A set of unique elements.
The element type needs to be an instance of the same Key
typeclass that
is used for keys in the Map
type above. Instances are already provided
for many common element types.
Set
implements Foldable
, Monoid
, etc so many common operations such
as foldr
to walk the elements and reduce them, length
to return the
size of the collection, null
to test whether is empty, and (<>
) to take
the union of two sets are available.
To convert to other collection types see fromSet
below.
(this is a thin wrapper around unordered-containers's
HashSet
, but if you use the conversion functions to extract
a list the list will be ordered according to the elements' Ord
instance)
Instances
Foldable Set Source # | |
Defined in Core.Data.Structures fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Key ε => Monoid (Set ε) Source # | |
Key ε => Semigroup (Set ε) Source # | |
Show ε => Show (Set ε) Source # | |
Key ε => Collection (Set ε) Source # | |
Eq ε => Eq (Set ε) Source # | |
type E (Set ε) Source # | |
Defined in Core.Data.Structures |
emptySet :: Key ε => Set ε Source #
An empty collection. This is used for example as an inital value when
building up a Set
using a fold.
singletonSet :: Key ε => ε -> Set ε Source #
Construct a collection comprising only the supplied element.
insertElement :: Key ε => ε -> Set ε -> Set ε Source #
Insert a new element into the collection. Since the Set
type does not
allow duplicates, inserting an element already in the collection has no
effect.
containsElement :: Key ε => ε -> Set ε -> Bool Source #
Does the collection contain the specified element?
removeElement :: Key ε => ε -> Set ε -> Set ε Source #
Remove an element from the collection if present.
Since: 0.3.7
Conversions
class Collection α where Source #
Types that represent collections of elements that can be converted to
Set
s. Haskell's ecosystem has several such. This typeclass provides an
adaptor to convert between them.
This typeclass also provides a mechanism to serialize a Set
out to a
Haskell list. The list will be ordered according to the Ord
instance of
the element type.
Instances are provided for containers's Set
and
unordered-containers's HashSet
in addition to the
instance for [ε]
lists described above.
Instances
Key ε => Collection (Set ε) Source # | from Data.Set |
Key ε => Collection (Set ε) Source # | |
Key ε => Collection (HashSet ε) Source # | from Data.HashSet |
Key ε => Collection [ε] Source # | |
Internals
class (Hashable κ, Ord κ) => Key κ Source #
Types that can be used as keys in dictionaries or elements in collections.
To be an instance of Key
a type must implement both Hashable
and Ord
.
This requirement means we can subsequently offer easy conversion
between different the dictionary and collection types you might encounter
when interacting with other libraries.
Instances for this library's Rope
and Bytes
are provided here, along
with many other common types.
Instances
Key ThreadId Source # | |
Defined in Core.Data.Structures | |
Key ByteString Source # | |
Defined in Core.Data.Structures | |
Key JsonKey Source # | |
Defined in Core.Encoding.Json | |
Key Bytes Source # | |
Defined in Core.Data.Structures | |
Key Rope Source # | |
Defined in Core.Data.Structures | |
Key Text Source # | |
Defined in Core.Data.Structures | |
Key Text Source # | |
Defined in Core.Data.Structures | |
Key String Source # | |
Defined in Core.Data.Structures | |
Key Char Source # | |
Defined in Core.Data.Structures | |
Key Int Source # | |
Defined in Core.Data.Structures |