dependent-hashmap-0.1.0.1: Dependent hash maps

Safe HaskellNone
LanguageHaskell2010

Data.Dependent.HashMap

Contents

Description

A map from hashable keys to values where the keys can specify the type of value that is associated with them. A map cannot contain duplicate keys; each key can map to at most one value. A DHashMap makes no guarantees as to the order of its elements.

The interface mirrors that of HashMap, with small adjustments and additions. The implementation is a thin layer on top of HashMap.

The implementation is based on hash array mapped tries. A DHashMap is often faster than other tree-based set types, especially when key comparison is expensive, as in the case of strings.

Many operations have a average-case complexity of O(log n). The implementation uses a large base (i.e. 16) so in practice these operations are constant time.

Synopsis

Documentation

data DHashMap k v Source #

A map from keys k to values v where k and v are indexed types and where every key-value pair is indexed by the same type.

Instances
(GEq k, Hashable (Some k)) => IsList (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

Associated Types

type Item (DHashMap k v) :: Type #

Methods

fromList :: [Item (DHashMap k v)] -> DHashMap k v #

fromListN :: Int -> [Item (DHashMap k v)] -> DHashMap k v #

toList :: DHashMap k v -> [Item (DHashMap k v)] #

(GEq k, Has' Eq k v) => Eq (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

Methods

(==) :: DHashMap k v -> DHashMap k v -> Bool #

(/=) :: DHashMap k v -> DHashMap k v -> Bool #

(GCompare k, Has' Eq k v, Has' Ord k v) => Ord (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

Methods

compare :: DHashMap k v -> DHashMap k v -> Ordering #

(<) :: DHashMap k v -> DHashMap k v -> Bool #

(<=) :: DHashMap k v -> DHashMap k v -> Bool #

(>) :: DHashMap k v -> DHashMap k v -> Bool #

(>=) :: DHashMap k v -> DHashMap k v -> Bool #

max :: DHashMap k v -> DHashMap k v -> DHashMap k v #

min :: DHashMap k v -> DHashMap k v -> DHashMap k v #

(GEq k, GRead k, Has' Read k v, Hashable (Some k)) => Read (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

(GShow k, Has' Show k v) => Show (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

Methods

showsPrec :: Int -> DHashMap k v -> ShowS #

show :: DHashMap k v -> String #

showList :: [DHashMap k v] -> ShowS #

(GEq k, Hashable (Some k)) => Semigroup (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

Methods

(<>) :: DHashMap k v -> DHashMap k v -> DHashMap k v #

sconcat :: NonEmpty (DHashMap k v) -> DHashMap k v #

stimes :: Integral b => b -> DHashMap k v -> DHashMap k v #

(GEq k, Hashable (Some k)) => Monoid (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

Methods

mempty :: DHashMap k v #

mappend :: DHashMap k v -> DHashMap k v -> DHashMap k v #

mconcat :: [DHashMap k v] -> DHashMap k v #

type Item (DHashMap k v) Source # 
Instance details

Defined in Data.Dependent.HashMap

type Item (DHashMap k v) = DSum k v

Construction

empty :: DHashMap k v Source #

O(1) Construct an empty map.

singleton :: Hashable (Some k) => k a -> v a -> DHashMap k v Source #

O(1) Construct a map with a single element.

Basic interface

null :: DHashMap k v -> Bool Source #

O(1) Return True if this map is empty, False otherwise.

size :: DHashMap k v -> Int Source #

O(n) Return the number of key-value mappings in this map.

member :: (GEq k, Hashable (Some k)) => k a -> DHashMap k v -> Bool Source #

O(log n) Return True if the specified key is present in the map, False otherwise.

lookup :: (GEq k, Hashable (Some k)) => k a -> DHashMap k v -> Maybe (v a) Source #

O(log n) Return the value to which the specified key is mapped, or Nothing if this map contains no mapping for the key.

lookupDefault :: (GEq k, Hashable (Some k)) => v a -> k a -> DHashMap k v -> v a Source #

O(log n) Return the value to which the specified key is mapped, or the default value if this map contains no mapping for the key.

(!) :: (GEq k, Hashable (Some k)) => DHashMap k v -> k a -> v a Source #

O(log n) Return the value to which the specified key is mapped. Calls error if this map contains no mapping for the key.

insert :: (GEq k, Hashable (Some k)) => k a -> v a -> DHashMap k v -> DHashMap k v Source #

O(log n) Associate the specified value with the specified key in this map. If this map previously contained a mapping for the key, the old value is replaced.

insertWith :: (GEq k, Hashable (Some k)) => (v a -> v a -> v a) -> k a -> v a -> DHashMap k v -> DHashMap k v Source #

O(log n) Associate the value with the key in this map. If this map previously contained a mapping for the key, the old value is replaced by the result of applying the given function to the new and old value. Example:

insertWith f k v map
  where f new old = new + old

delete :: (GEq k, Hashable (Some k)) => k a -> DHashMap k v -> DHashMap k v Source #

O(log n) Remove the mapping for the specified key from this map if present.

adjust :: (GEq k, Hashable (Some k)) => (v a -> v a) -> k a -> DHashMap k v -> DHashMap k v Source #

O(log n) Adjust the value tied to a given key in this map only if it is present. Otherwise, leave the map alone.

update :: (GEq k, Hashable (Some k)) => (v a -> Maybe (v a)) -> k a -> DHashMap k v -> DHashMap k v Source #

O(log n) The expression (update f k map) updates the value x at k, (if it is in the map). If (f k x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

alter :: (GEq k, Hashable (Some k)) => (Maybe (v a) -> Maybe (v a)) -> k a -> DHashMap k v -> DHashMap k v Source #

O(log n) The expression (alter f k map) alters the value x at k, or absence thereof. alter can be used to insert, delete, or update a value in a map. In short : lookup k (alter f k m) = f (lookup k m).

alterF :: (Functor f, GEq k, Hashable (Some k)) => (Maybe (v a) -> f (Maybe (v a))) -> k a -> DHashMap k v -> f (DHashMap k v) Source #

O(log n) The expression (alterF f k map) alters the value x at k, or absence thereof. alterF can be used to insert, delete, or update a value in a map.

alterLookup :: (GEq k, Hashable (Some k)) => (Maybe (v a) -> Maybe (v a)) -> k a -> DHashMap k v -> (Maybe (v a), DHashMap k v) Source #

O(log n) alterLookup f k map looks up the value at k, if any, and alters it, in one operation.

alterLookup f k map = (lookup k map, alter f k map)

Union

union :: (GEq k, Hashable (Some k)) => DHashMap k v -> DHashMap k v -> DHashMap k v Source #

O(n+m) The union of two maps. If a key occurs in both maps, the mapping from the first will be the mapping in the result.

unionWith :: (GEq k, Hashable (Some k)) => (forall a. v a -> v a -> v a) -> DHashMap k v -> DHashMap k v -> DHashMap k v Source #

O(n+m) The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.

unionWithKey :: (GEq k, Hashable (Some k)) => (forall a. k a -> v a -> v a -> v a) -> DHashMap k v -> DHashMap k v -> DHashMap k v Source #

O(n+m) The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.

unions :: (GEq k, Hashable (Some k), Foldable f) => f (DHashMap k v) -> DHashMap k v Source #

The union of a list of maps.

unionsWith :: (GEq k, Hashable (Some k), Foldable f) => (forall a. v a -> v a -> v a) -> f (DHashMap k v) -> DHashMap k v Source #

The union of a list of maps, with combining operation.

unionsWithKey :: (GEq k, Hashable (Some k), Foldable f) => (forall a. k a -> v a -> v a -> v a) -> f (DHashMap k v) -> DHashMap k v Source #

The union of a list of maps, with combining operation.

Transformations

map :: (forall a. v a -> v' a) -> DHashMap k v -> DHashMap k v' Source #

O(n) Transform this map by applying a function to every value.

mapWithKey :: (forall a. k a -> v a -> v' a) -> DHashMap k v -> DHashMap k v' Source #

O(n) Transform this map by applying a function to every value.

traverse :: Applicative f => (forall a. v a -> f (v' a)) -> DHashMap k v -> f (DHashMap k v') Source #

O(n) Perform an Applicative action for each value in a map and produce a map of all the results.

Note: the order in which the actions occur is unspecified. In particular, when the map contains hash collisions, the order in which the actions associated with the keys involved will depend in an unspecified way on their insertion order.

traverseWithKey :: Applicative f => (forall a. k a -> v a -> f (v' a)) -> DHashMap k v -> f (DHashMap k v') Source #

O(n) Perform an Applicative action for each key-value pair in a map and produce a map of all the results.

Note: the order in which the actions occur is unspecified. In particular, when the map contains hash collisions, the order in which the actions associated with the keys involved will depend in an unspecified way on their insertion order.

Difference and intersection

difference :: (GEq k, Hashable (Some k)) => DHashMap k v -> DHashMap k v' -> DHashMap k v Source #

O(n*log m) Difference of two maps. Return elements of the first map not existing in the second.

differenceWith :: (GEq k, Hashable (Some k)) => (forall a. v a -> v' a -> Maybe (v a)) -> DHashMap k v -> DHashMap k v' -> DHashMap k v Source #

O(n*log m) Difference with a combining function. When two equal keys are encountered, the combining function is applied to the values of these keys. If it returns Nothing, the element is discarded (proper set difference). If it returns (Just y), the element is updated with a new value y.

differenceWithKey :: (GEq k, Hashable (Some k)) => (forall a. k a -> v a -> v' a -> Maybe (v a)) -> DHashMap k v -> DHashMap k v' -> DHashMap k v Source #

O(n*log m) Difference with a combining function. When two equal keys are encountered, the combining function is applied to the key and the values of these keys. If it returns Nothing, the element is discarded (proper set difference). If it returns (Just y), the element is updated with a new value y.

intersection :: (GEq k, Hashable (Some k)) => DHashMap k v -> DHashMap k v' -> DHashMap k v Source #

O(n*log m) Intersection of two maps. Return elements of the first map for keys existing in the second.

intersectionWith :: (GEq k, Hashable (Some k)) => (forall a. v1 a -> v2 a -> v3 a) -> DHashMap k v1 -> DHashMap k v2 -> DHashMap k v3 Source #

O(n+m) Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.

intersectionWithKey :: (GEq k, Hashable (Some k)) => (forall a. k a -> v1 a -> v2 a -> v3 a) -> DHashMap k v1 -> DHashMap k v2 -> DHashMap k v3 Source #

O(n+m) Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.

Folds

foldMap :: Monoid m => (forall a. v a -> m) -> DHashMap k v -> m Source #

Map each value of the map to a monoid, and combine the results.

foldMapWithKey :: Monoid m => (forall a. k a -> v a -> m) -> DHashMap k v -> m Source #

Map each key-value pair of the map to a monoid, and combine the results.

foldl :: (forall a. b -> v a -> b) -> b -> DHashMap k v -> b Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator).

foldlWithKey :: (forall a. b -> k a -> v a -> b) -> b -> DHashMap k v -> b Source #

O(n) Reduce this map by applying a binary operator to all key-value pairs, using the given starting value (typically the left-identity of the operator).

foldl' :: (forall a. b -> v a -> b) -> b -> DHashMap k v -> b Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldlWithKey' :: (forall a. b -> k a -> v a -> b) -> b -> DHashMap k v -> b Source #

O(n) Reduce this map by applying a binary operator to all key-value pairs, using the given starting value (typically the left-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldr :: (forall a. v a -> b -> b) -> b -> DHashMap k v -> b Source #

O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).

foldrWithKey :: (forall a. k a -> v a -> b -> b) -> b -> DHashMap k v -> b Source #

O(n) Reduce this map by applying a binary operator to all key-value pairs, using the given starting value (typically the right-identity of the operator).

Filter

filter :: (forall a. v a -> Bool) -> DHashMap k v -> DHashMap k v Source #

O(n) Filter this map by retaining values that satisfy a predicate.

filterWithKey :: (forall a. k a -> v a -> Bool) -> DHashMap k v -> DHashMap k v Source #

O(n) Filter this map by retaining only key-value pairs satisfying a predicate.

mapMaybe :: (forall a. v1 a -> Maybe (v2 a)) -> DHashMap k v1 -> DHashMap k v2 Source #

O(n) Transform this map by applying a function to every value and retaining only the Just results.

mapMaybeWithKey :: (forall a. k a -> v1 a -> Maybe (v2 a)) -> DHashMap k v1 -> DHashMap k v2 Source #

O(n) Transform this map by applying a function to every key-value pair and retaining only the Just results.

Conversions

keys :: DHashMap k v -> [Some k] Source #

O(n) Return a list of this map's keys. The list is produced lazily.

elems :: DHashMap k v -> [Some v] Source #

O(n) Return a list of this map's values. The list is produced lazily.

Lists

toList :: DHashMap k v -> [DSum k v] Source #

O(n) Return a list of this map's elements. The list is produced lazily. The order of its elements is unspecified.

fromList :: (GEq k, Hashable (Some k)) => [DSum k f] -> DHashMap k f Source #

O(n) Construct a map with the supplied mappings. If the list contains duplicate mappings, the later mappings take precedence.

fromListWith :: (GEq k, Hashable (Some k)) => (forall a. v a -> v a -> v a) -> [DSum k v] -> DHashMap k v Source #

O(n*log n) Construct a map from a list of elements. Uses the provided function to merge duplicate entries.

fromListWithKey :: (GEq k, Hashable (Some k)) => (forall a. k a -> v a -> v a -> v a) -> [DSum k v] -> DHashMap k v Source #

O(n*log n) Construct a map from a list of elements. Uses the provided function to merge duplicate entries.

Re-exports

data DSum (tag :: k -> Type) (f :: k -> Type) :: forall k. (k -> Type) -> (k -> Type) -> Type where #

A basic dependent sum type; the first component is a tag that specifies the type of the second; for example, think of a GADT such as:

data Tag a where
   AString :: Tag String
   AnInt   :: Tag Int

Then, we have the following valid expressions of type Applicative f => DSum Tag f:

AString ==> "hello!"
AnInt   ==> 42

And we can write functions that consume DSum Tag f values by matching, such as:

toString :: DSum Tag Identity -> String
toString (AString :=> Identity str) = str
toString (AnInt   :=> Identity int) = show int

By analogy to the (key => value) construction for dictionary entries in many dynamic languages, we use (key :=> value) as the constructor for dependent sums. The :=> and ==> operators have very low precedence and bind to the right, so if the Tag GADT is extended with an additional constructor Rec :: Tag (DSum Tag Identity), then Rec ==> AnInt ==> 3 + 4 is parsed as would be expected (Rec ==> (AnInt ==> (3 + 4))) and has type DSum Identity Tag. Its precedence is just above that of $, so foo bar $ AString ==> "eep" is equivalent to foo bar (AString ==> "eep").

Constructors

(:=>) :: forall k (tag :: k -> Type) (f :: k -> Type) (a :: k). !(tag a) -> f a -> DSum tag f infixr 1 
Instances
(GEq tag, Has' Eq tag f) => Eq (DSum tag f) 
Instance details

Defined in Data.Dependent.Sum

Methods

(==) :: DSum tag f -> DSum tag f -> Bool #

(/=) :: DSum tag f -> DSum tag f -> Bool #

(GCompare tag, Has' Eq tag f, Has' Ord tag f) => Ord (DSum tag f) 
Instance details

Defined in Data.Dependent.Sum

Methods

compare :: DSum tag f -> DSum tag f -> Ordering #

(<) :: DSum tag f -> DSum tag f -> Bool #

(<=) :: DSum tag f -> DSum tag f -> Bool #

(>) :: DSum tag f -> DSum tag f -> Bool #

(>=) :: DSum tag f -> DSum tag f -> Bool #

max :: DSum tag f -> DSum tag f -> DSum tag f #

min :: DSum tag f -> DSum tag f -> DSum tag f #

(GRead tag, Has' Read tag f) => Read (DSum tag f) 
Instance details

Defined in Data.Dependent.Sum

Methods

readsPrec :: Int -> ReadS (DSum tag f) #

readList :: ReadS [DSum tag f] #

readPrec :: ReadPrec (DSum tag f) #

readListPrec :: ReadPrec [DSum tag f] #

(GShow tag, Has' Show tag f) => Show (DSum tag f) 
Instance details

Defined in Data.Dependent.Sum

Methods

showsPrec :: Int -> DSum tag f -> ShowS #

show :: DSum tag f -> String #

showList :: [DSum tag f] -> ShowS #

data Some (tag :: k -> Type) :: forall k. (k -> Type) -> Type where #

Existential. This is type is useful to hide GADTs' parameters.

>>> data Tag :: * -> * where TagInt :: Tag Int; TagBool :: Tag Bool
>>> instance GShow Tag where gshowsPrec _ TagInt = showString "TagInt"; gshowsPrec _ TagBool = showString "TagBool"

You can either use PatternSynonyms

>>> let x = Some TagInt
>>> x
Some TagInt
>>> case x of { Some TagInt -> "I"; Some TagBool -> "B" } :: String
"I"

or you can use functions

>>> let y = mkSome TagBool
>>> y
Some TagBool
>>> withSome y $ \y' -> case y' of { TagInt -> "I"; TagBool -> "B" } :: String
"B"

The implementation of mapSome is safe.

>>> let f :: Tag a -> Tag a; f TagInt = TagInt; f TagBool = TagBool
>>> mapSome f y
Some TagBool

but you can also use:

>>> withSome y (mkSome . f)
Some TagBool

Bundled Patterns

pattern Some :: forall k (tag :: k -> Type). () => forall (a :: k). tag a -> Some tag 
Instances
GEq tag => Eq (Some tag) 
Instance details

Defined in Data.Some

Methods

(==) :: Some tag -> Some tag -> Bool #

(/=) :: Some tag -> Some tag -> Bool #

GCompare tag => Ord (Some tag) 
Instance details

Defined in Data.Some

Methods

compare :: Some tag -> Some tag -> Ordering #

(<) :: Some tag -> Some tag -> Bool #

(<=) :: Some tag -> Some tag -> Bool #

(>) :: Some tag -> Some tag -> Bool #

(>=) :: Some tag -> Some tag -> Bool #

max :: Some tag -> Some tag -> Some tag #

min :: Some tag -> Some tag -> Some tag #

GRead f => Read (Some f) 
Instance details

Defined in Data.Some

GShow tag => Show (Some tag) 
Instance details

Defined in Data.Some

Methods

showsPrec :: Int -> Some tag -> ShowS #

show :: Some tag -> String #

showList :: [Some tag] -> ShowS #