core-data-0.3.3.1: Convenience wrappers around common data structures and encodings
Safe HaskellNone
LanguageHaskell2010

Core.Data.Structures

Description

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

Map type

data Map κ ν Source #

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

Instances details
Bifoldable Map Source # 
Instance details

Defined in Core.Data.Structures

Methods

bifold :: Monoid m => Map m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Map a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Map a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Map a b -> c #

Foldable (Map κ) Source # 
Instance details

Defined in Core.Data.Structures

Methods

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 #

toList :: Map κ a -> [a] #

null :: Map κ a -> Bool #

length :: Map κ a -> Int #

elem :: Eq a => a -> Map κ a -> Bool #

maximum :: Ord a => Map κ a -> a #

minimum :: Ord a => Map κ a -> a #

sum :: Num a => Map κ a -> a #

product :: Num a => Map κ a -> a #

Key κ => IsList (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type Item (Map κ ν) #

Methods

fromList :: [Item (Map κ ν)] -> Map κ ν #

fromListN :: Int -> [Item (Map κ ν)] -> Map κ ν #

toList :: Map κ ν -> [Item (Map κ ν)] #

(Eq κ, Eq ν) => Eq (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Methods

(==) :: Map κ ν -> Map κ ν -> Bool #

(/=) :: Map κ ν -> Map κ ν -> Bool #

(Show κ, Show ν) => Show (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Methods

showsPrec :: Int -> Map κ ν -> ShowS #

show :: Map κ ν -> String #

showList :: [Map κ ν] -> ShowS #

Key κ => Semigroup (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Methods

(<>) :: Map κ ν -> Map κ ν -> Map κ ν #

sconcat :: NonEmpty (Map κ ν) -> Map κ ν #

stimes :: Integral b => b -> Map κ ν -> Map κ ν #

Key κ => Monoid (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Methods

mempty :: Map κ ν #

mappend :: Map κ ν -> Map κ ν -> Map κ ν #

mconcat :: [Map κ ν] -> Map κ ν #

Key κ => Dictionary (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type K (Map κ ν) Source #

type V (Map κ ν) Source #

Methods

fromMap :: Map (K (Map κ ν)) (V (Map κ ν)) -> Map κ ν Source #

intoMap :: Map κ ν -> Map (K (Map κ ν)) (V (Map κ ν)) Source #

type Item (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

type Item (Map κ ν) = (κ, ν)
type K (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

type K (Map κ ν) = κ
type V (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

type V (Map κ ν) = ν

emptyMap :: Map κ ν Source #

A dictionary with no key/value mappings.

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.

containsKey :: Key κ => κ -> Map κ ν -> Bool Source #

Does the dictionary contain the specified key?

lookupKeyValue :: Key κ => κ -> Map κ ν -> Maybe ν Source #

If the dictionary contains the specified key, return the value associated with that key.

Conversions

class Dictionary α where Source #

Types that represent key/value pairs that can be converted to Maps. 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.

Associated Types

type K α :: Type Source #

type V α :: Type Source #

Methods

fromMap :: Map (K α) (V α) -> α Source #

intoMap :: α -> Map (K α) (V α) Source #

Instances

Instances details
Key κ => Dictionary [(κ, ν)] Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type K [(κ, ν)] Source #

type V [(κ, ν)] Source #

Methods

fromMap :: Map (K [(κ, ν)]) (V [(κ, ν)]) -> [(κ, ν)] Source #

intoMap :: [(κ, ν)] -> Map (K [(κ, ν)]) (V [(κ, ν)]) Source #

Key κ => Dictionary (Map κ ν) Source #

from Data.Map.Strict (and .Lazy)

Instance details

Defined in Core.Data.Structures

Associated Types

type K (Map κ ν) Source #

type V (Map κ ν) Source #

Methods

fromMap :: Map0 (K (Map κ ν)) (V (Map κ ν)) -> Map κ ν Source #

intoMap :: Map κ ν -> Map0 (K (Map κ ν)) (V (Map κ ν)) Source #

Key κ => Dictionary (HashMap κ ν) Source #

from Data.HashMap.Strict (and .Lazy)

Instance details

Defined in Core.Data.Structures

Associated Types

type K (HashMap κ ν) Source #

type V (HashMap κ ν) Source #

Methods

fromMap :: Map (K (HashMap κ ν)) (V (HashMap κ ν)) -> HashMap κ ν Source #

intoMap :: HashMap κ ν -> Map (K (HashMap κ ν)) (V (HashMap κ ν)) Source #

Key κ => Dictionary (Map κ ν) Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type K (Map κ ν) Source #

type V (Map κ ν) Source #

Methods

fromMap :: Map (K (Map κ ν)) (V (Map κ ν)) -> Map κ ν Source #

intoMap :: Map κ ν -> Map (K (Map κ ν)) (V (Map κ ν)) Source #

Set type

data Set ε Source #

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

Instances details
Foldable Set Source # 
Instance details

Defined in Core.Data.Structures

Methods

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 #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

Eq ε => Eq (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

Methods

(==) :: Set ε -> Set ε -> Bool #

(/=) :: Set ε -> Set ε -> Bool #

Show ε => Show (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

Methods

showsPrec :: Int -> Set ε -> ShowS #

show :: Set ε -> String #

showList :: [Set ε] -> ShowS #

Key ε => Semigroup (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

Methods

(<>) :: Set ε -> Set ε -> Set ε #

sconcat :: NonEmpty (Set ε) -> Set ε #

stimes :: Integral b => b -> Set ε -> Set ε #

Key ε => Monoid (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

Methods

mempty :: Set ε #

mappend :: Set ε -> Set ε -> Set ε #

mconcat :: [Set ε] -> Set ε #

Key ε => Collection (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type E (Set ε) Source #

Methods

fromSet :: Set (E (Set ε)) -> Set ε Source #

intoSet :: Set ε -> Set (E (Set ε)) Source #

type E (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

type E (Set ε) = ε

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?

Conversions

class Collection α where Source #

Types that represent collections of elements that can be converted to Sets. 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.

Associated Types

type E α :: Type Source #

Methods

fromSet :: Set (E α) -> α Source #

intoSet :: α -> Set (E α) Source #

Instances

Instances details
Key ε => Collection [ε] Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type E [ε] Source #

Methods

fromSet :: Set (E [ε]) -> [ε] Source #

intoSet :: [ε] -> Set (E [ε]) Source #

Key ε => Collection (Set ε) Source #

from Data.Set

Instance details

Defined in Core.Data.Structures

Associated Types

type E (Set ε) Source #

Methods

fromSet :: Set0 (E (Set ε)) -> Set ε Source #

intoSet :: Set ε -> Set0 (E (Set ε)) Source #

Key ε => Collection (HashSet ε) Source #

from Data.HashSet

Instance details

Defined in Core.Data.Structures

Associated Types

type E (HashSet ε) Source #

Methods

fromSet :: Set (E (HashSet ε)) -> HashSet ε Source #

intoSet :: HashSet ε -> Set (E (HashSet ε)) Source #

Key ε => Collection (Set ε) Source # 
Instance details

Defined in Core.Data.Structures

Associated Types

type E (Set ε) Source #

Methods

fromSet :: Set (E (Set ε)) -> Set ε Source #

intoSet :: Set ε -> Set (E (Set ε)) 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

Instances details
Key Char Source # 
Instance details

Defined in Core.Data.Structures

Key Int Source # 
Instance details

Defined in Core.Data.Structures

Key String Source # 
Instance details

Defined in Core.Data.Structures

Key ByteString Source # 
Instance details

Defined in Core.Data.Structures

Key Text Source # 
Instance details

Defined in Core.Data.Structures

Key Text Source # 
Instance details

Defined in Core.Data.Structures

Key Rope Source # 
Instance details

Defined in Core.Data.Structures

Key Bytes Source # 
Instance details

Defined in Core.Data.Structures

Key JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

unMap :: Map κ ν -> HashMap κ ν Source #

unSet :: Set ε -> HashSet ε Source #