-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Persistent containers HashMap and HashSet. -- -- An implementation of persistent HashMap and HashSet on -- top of Data.IntMap.IntMap and Data.IntSet.IntSet, with -- very similar API. -- -- The class Hashable is providing the Hashable.hash -- method. -- -- The HashMap key value is an Data.IntMap.IntMap -- indexed by the hash value, containing Data.Map.Map key -- value for all keys with the same hash value. -- -- The HashSet elem is an Data.IntMap.IntMap -- indexed by the hash value, containing Data.Set.Set -- elem for all elements with the same hash value. @package hashmap @version 1.0.0.2 -- | Hashable class for hashable types, with instances for basic -- types. The only function of this class is -- --
--   hash :: Hashable h => h -> Int
--   
-- -- The hash function should be as collision-free as possible, the -- probability of hash a == hash b should ideally -- be 1 over the number of representable values in an Int. -- -- Returning an Int is a result of the Data.IntMap.IntMap -- using Int as a key, as inserting the hash values to the -- Data.IntMap.IntMap was the purpose of creating this class. module Data.Hashable -- | The class containing a function hash which computes the hash -- values of given value. class Hashable a hash :: (Hashable a) => a -> Int -- | Combines two given hash values. combine :: Int -> Int -> Int instance Hashable ByteString instance Hashable ByteString instance (Hashable a) => Hashable [a] instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) instance (Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) instance (Hashable a1, Hashable a2) => Hashable (a1, a2) instance (Hashable a) => Hashable (Maybe a) instance Hashable Char instance Hashable Word64 instance Hashable Word32 instance Hashable Word16 instance Hashable Word8 instance Hashable Word instance Hashable Int64 instance Hashable Int32 instance Hashable Int16 instance Hashable Int8 instance Hashable Int instance Hashable Bool instance Hashable () -- | Persistent HashMap, which is defined as -- --
--   data HashMap k v = Data.IntMap.IntMap (Data.Map.Map k v)
--   
-- -- is an Data.IntMap.IntMap indexed by hash values of keys, -- containing a map Data.Map.Map k v with keys of the -- same hash values. -- -- The interface of a HashMap is a suitable subset of -- Data.IntMap.IntMap. -- -- The complexity of operations is determined by the complexities of -- Data.IntMap.IntMap and Data.Map.Map operations. See -- the sources of HashMap to see which operations from -- containers package are used. module Data.HashMap -- | The abstract type of a HashMap. Its interface is a suitable -- subset of Data.IntMap.IntMap. data HashMap k v -- | Find the value at a key. Calls error when the element can not -- be found. (!) :: (Hashable k, Ord k) => HashMap k a -> k -> a -- | Same as difference. (\\) :: (Ord k) => HashMap k a -> HashMap k b -> HashMap k a -- | Is the map empty? null :: HashMap k a -> Bool -- | Number of elements in the map. size :: HashMap k a -> Int -- | Is the key a member of the map? member :: (Hashable k, Ord k) => k -> HashMap k a -> Bool -- | Is the key not a member of the map? notMember :: (Hashable k, Ord k) => k -> HashMap k a -> Bool -- | Lookup the value at a key in the map. lookup :: (Hashable k, Ord k) => k -> HashMap k a -> Maybe a -- | The expression (findWithDefault def k map) returns the -- value at key k or returns def when the key is not an -- element of the map. findWithDefault :: (Hashable k, Ord k) => a -> k -> HashMap k a -> a -- | The empty map. empty :: HashMap k a -- | A map of one element. singleton :: (Hashable k) => k -> a -> HashMap k a -- | Insert a new key/value pair in the map. If the key is already present -- in the map, the associated value is replaced with the supplied value, -- i.e. insert is equivalent to insertWith -- const. insert :: (Hashable k, Ord k) => k -> a -> HashMap k a -> HashMap k a -- | Insert with a combining function. insertWith f key value -- mp will insert the pair (key, value) into mp if key does -- not exist in the map. If the key does exist, the function will insert -- f new_value old_value. insertWith :: (Hashable k, Ord k) => (a -> a -> a) -> k -> a -> HashMap k a -> HashMap k a -- | Insert with a combining function. insertWithKey f key value -- mp will insert the pair (key, value) into mp if key does -- not exist in the map. If the key does exist, the function will insert -- f key new_value old_value. insertWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> HashMap k a -> HashMap k a -- | The expression (insertLookupWithKey f k x map) is a -- pair where the first element is equal to (lookup k -- map) and the second element equal to (insertWithKey f -- k x map). insertLookupWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> HashMap k a -> (Maybe a, HashMap k a) -- | Delete a key and its value from the map. When the key is not a member -- of the map, the original map is returned. delete :: (Hashable k, Ord k) => k -> HashMap k a -> HashMap k a -- | Adjust a value at a specific key. When the key is not a member of the -- map, the original map is returned. adjust :: (Hashable k, Ord k) => (a -> a) -> k -> HashMap k a -> HashMap k a -- | Adjust a value at a specific key. When the key is not a member of the -- map, the original map is returned. adjustWithKey :: (Hashable k, Ord k) => (k -> a -> a) -> k -> HashMap k a -> HashMap k a -- | The expression (update f k map) updates the value -- x at k (if it is in the map). If (f x) is -- Nothing, the element is deleted. If it is (Just -- y), the key k is bound to the new value y. update :: (Hashable k, Ord k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a -- | 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. updateWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> HashMap k a -> HashMap k a -- | Lookup and update. The function returns original value, if it is -- updated. This is different behavior than -- Data.Map.updateLookupWithKey. Returns the original key value -- if the map entry is deleted. updateLookupWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> HashMap k a -> (Maybe a, HashMap k a) -- | 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 an HashMap. alter :: (Hashable k, Ord k) => (Maybe a -> Maybe a) -> k -> HashMap k a -> HashMap k a -- | The (left-biased) union of two maps. It prefers the first map when -- duplicate keys are encountered, i.e. (union == -- unionWith const). union :: (Ord k) => HashMap k a -> HashMap k a -> HashMap k a -- | The union with a combining function. unionWith :: (Ord k) => (a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a -- | The union with a combining function. unionWithKey :: (Ord k) => (k -> a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a -- | The union of a list of maps. unions :: (Ord k) => [HashMap k a] -> HashMap k a -- | The union of a list of maps, with a combining operation. unionsWith :: (Ord k) => (a -> a -> a) -> [HashMap k a] -> HashMap k a -- | Difference between two maps (based on keys). difference :: (Ord k) => HashMap k a -> HashMap k b -> HashMap k a -- | Difference with a combining function. differenceWith :: (Ord k) => (a -> b -> Maybe a) -> HashMap k a -> HashMap k b -> HashMap k a -- | Difference with a combining function. When two equal keys are -- encountered, the combining function is applied to the key and both -- values. 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 :: (Ord k) => (k -> a -> b -> Maybe a) -> HashMap k a -> HashMap k b -> HashMap k a -- | The (left-biased) intersection of two maps (based on keys). intersection :: (Ord k) => HashMap k a -> HashMap k b -> HashMap k a -- | The intersection with a combining function. intersectionWith :: (Ord k) => (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c -- | The intersection with a combining function. intersectionWithKey :: (Ord k) => (k -> a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c -- | Map a function over all values in the map. map :: (a -> b) -> HashMap k a -> HashMap k b -- | Map a function over all values in the map. mapWithKey :: (k -> a -> b) -> HashMap k a -> HashMap k b -- | The function mapAccum threads an accumulating argument -- through the map in unspecified order of keys. mapAccum :: (a -> b -> (a, c)) -> a -> HashMap k b -> (a, HashMap k c) -- | The function mapAccumWithKey threads an accumulating -- argument through the map in unspecified order of keys. mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> HashMap k b -> (a, HashMap k c) -- | Fold the values in the map, such that fold f z == -- foldr f z . elems. fold :: (a -> b -> b) -> b -> HashMap k a -> b -- | Fold the keys and values in the map, such that foldWithKey -- f z == foldr (uncurry f) z . toAscList. foldWithKey :: (k -> a -> b -> b) -> b -> HashMap k a -> b -- | Return all elements of the map in arbitrary order of their keys. elems :: HashMap k a -> [a] -- | Return all keys of the map in arbitrary order. keys :: HashMap k a -> [k] -- | The set of all keys of the map. keysSet :: (Ord k) => HashMap k a -> Set k -- | Return all key/value pairs in the map in arbitrary key order. assocs :: HashMap k a -> [(k, a)] -- | Convert the map to a list of key/value pairs. toList :: HashMap k a -> [(k, a)] -- | Create a map from a list of key/value pairs. fromList :: (Hashable k, Ord k) => [(k, a)] -> HashMap k a -- | Create a map from a list of key/value pairs with a combining function. fromListWith :: (Hashable k, Ord k) => (a -> a -> a) -> [(k, a)] -> HashMap k a -- | Build a map from a list of key/value pairs with a combining function. fromListWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> [(k, a)] -> HashMap k a -- | Filter all values that satisfy some predicate. filter :: (Ord k) => (a -> Bool) -> HashMap k a -> HashMap k a -- | Filter all keys/values that satisfy some predicate. filterWithKey :: (Ord k) => (k -> a -> Bool) -> HashMap k a -> HashMap k a -- | Partition the map according to some predicate. The first map contains -- all elements that satisfy the predicate, the second all elements that -- fail the predicate. partition :: (Ord k) => (a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a) -- | Partition the map according to some predicate. The first map contains -- all elements that satisfy the predicate, the second all elements that -- fail the predicate. partitionWithKey :: (Ord k) => (k -> a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a) -- | Map values and collect the Just results. mapMaybe :: (Ord k) => (a -> Maybe b) -> HashMap k a -> HashMap k b -- | Map keys/values and collect the Just results. mapMaybeWithKey :: (Ord k) => (k -> a -> Maybe b) -> HashMap k a -> HashMap k b -- | Map values and separate the Left and Right results. mapEither :: (Ord k) => (a -> Either b c) -> HashMap k a -> (HashMap k b, HashMap k c) -- | Map keys/values and separate the Left and Right results. mapEitherWithKey :: (Ord k) => (k -> a -> Either b c) -> HashMap k a -> (HashMap k b, HashMap k c) -- | Is this a submap? isSubmapOf :: (Ord k, Eq a) => HashMap k a -> HashMap k a -> Bool -- | The expression (isSubmapOfBy f m1 m2) returns -- True if all keys in m1 are in m2, and when -- f returns True when applied to their respective -- values. isSubmapOfBy :: (Ord k) => (a -> b -> Bool) -> HashMap k a -> HashMap k b -> Bool -- | Is this a proper submap? (ie. a submap but not equal). isProperSubmapOf :: (Ord k, Eq a) => HashMap k a -> HashMap k a -> Bool -- | Is this a proper submap? (ie. a submap but not equal). The expression -- (isProperSubmapOfBy f m1 m2) returns True when -- m1 and m2 are not equal, all keys in m1 are -- in m2, and when f returns True when applied -- to their respective values. isProperSubmapOfBy :: (Ord k) => (a -> b -> Bool) -> HashMap k a -> HashMap k b -> Bool instance (Eq k, Eq v) => Eq (HashMap k v) instance (Ord k, Ord v) => Ord (HashMap k v) instance (Data k, Hashable k, Ord k, Data a) => Data (HashMap k a) instance Typeable2 HashMap instance (Read k, Hashable k, Ord k, Read a) => Read (HashMap k a) instance (Show k, Show a) => Show (HashMap k a) instance Traversable (HashMap k) instance Foldable (HashMap k) instance (Ord k) => Monoid (HashMap k a) instance Functor (HashMap k) -- | Persistent HashSet, which is defined as -- --
--   data HashSet e = Data.IntMap.IntMap (Data.Set.Set e)
--   
-- -- is an Data.IntMap.IntMap indexed by hash values of elements, -- containing a set Data.Set.Set e with elements of the -- same hash values. -- -- The interface of a HashSet is a suitable subset of -- Data.IntSet.IntSet. -- -- The complexity of operations is determined by the complexities of -- Data.IntMap.IntMap and Data.Set.Set operations. See -- the sources of HashSet to see which operations from -- containers package are used. module Data.HashSet -- | The abstract type of a HashSet. Its interface is a suitable -- subset of Data.IntSet.IntSet. data HashSet a -- | Same as difference. (\\) :: (Ord a) => HashSet a -> HashSet a -> HashSet a -- | Is the set empty? null :: HashSet a -> Bool -- | Number of elements in the set. size :: HashSet a -> Int -- | Is the element a member of the set? member :: (Hashable a, Ord a) => a -> HashSet a -> Bool -- | Is the element not a member of the set? notMember :: (Hashable a, Ord a) => a -> HashSet a -> Bool -- | Is this a subset? isSubsetOf :: (Ord a) => HashSet a -> HashSet a -> Bool -- | Is this a proper subset? (ie. a subset but not equal). isProperSubsetOf :: (Ord a) => HashSet a -> HashSet a -> Bool -- | The empty set. empty :: HashSet a -- | A set of one element. singleton :: (Hashable a) => a -> HashSet a -- | Add a value to the set. When the value is already an element of the -- set, it is replaced by the new one, ie. insert is left-biased. insert :: (Hashable a, Ord a) => a -> HashSet a -> HashSet a -- | Delete a value in the set. Returns the original set when the value was -- not present. delete :: (Hashable a, Ord a) => a -> HashSet a -> HashSet a -- | The union of two sets. union :: (Ord a) => HashSet a -> HashSet a -> HashSet a -- | The union of a list of sets. unions :: (Ord a) => [HashSet a] -> HashSet a -- | Difference between two sets. difference :: (Ord a) => HashSet a -> HashSet a -> HashSet a -- | The intersection of two sets. intersection :: (Ord a) => HashSet a -> HashSet a -> HashSet a -- | Filter all elements that satisfy some predicate. filter :: (Ord a) => (a -> Bool) -> HashSet a -> HashSet a -- | Partition the set according to some predicate. The first set contains -- all elements that satisfy the predicate, the second all elements that -- fail the predicate. partition :: (Ord a) => (a -> Bool) -> HashSet a -> (HashSet a, HashSet a) -- | map f s is the set obtained by applying f to -- each element of s. -- -- It's worth noting that the size of the result may be smaller if, for -- some (x,y), x /= y && f x == f y map :: (Hashable b, Ord b) => (a -> b) -> HashSet a -> HashSet b -- | Fold over the elements of a set in an unspecified order. fold :: (a -> b -> b) -> b -> HashSet a -> b -- | The elements of a set. (For sets, this is equivalent to toList). elems :: HashSet a -> [a] -- | Convert the set to a list of elements. toList :: HashSet a -> [a] -- | Create a set from a list of elements. fromList :: (Hashable a, Ord a) => [a] -> HashSet a instance (Eq a) => Eq (HashSet a) instance (Ord a) => Ord (HashSet a) instance (Hashable a, Ord a, Data a) => Data (HashSet a) instance Typeable1 HashSet instance (Hashable a, Ord a, Read a) => Read (HashSet a) instance (Show a) => Show (HashSet a) instance (Ord a) => Monoid (HashSet a)