Copyright | © 2022–2024 Jonathan Knowles |
---|---|
License | Apache-2.0 |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Provides the MultiMap
class, which models a total relation from unique
keys to sets of values.
Synopsis
- class (Eq (m k v), Ord k, Ord v) => MultiMap m k v where
- fromList :: [(k, Set v)] -> m k v
- toList :: m k v -> [(k, Set v)]
- empty :: m k v
- lookup :: k -> m k v -> Set v
- null :: m k v -> Bool
- nonNull :: m k v -> Bool
- nonNullKey :: k -> m k v -> Bool
- nonNullKeys :: m k v -> Set k
- nonNullCount :: m k v -> Int
- isSubmapOf :: m k v -> m k v -> Bool
- update :: k -> Set v -> m k v -> m k v
- insert :: k -> Set v -> m k v -> m k v
- remove :: k -> Set v -> m k v -> m k v
- union :: m k v -> m k v -> m k v
- intersection :: m k v -> m k v -> m k v
Documentation
class (Eq (m k v), Ord k, Ord v) => MultiMap m k v where Source #
Models a total relation from unique keys to sets of values.
fromList :: [(k, Set v)] -> m k v Source #
Constructs a multimap from a list of key to value set mappings.
Removing empty sets from the input list does not affect the result:
fromList ≡ fromList . filter ((/= Set.empty) . snd)
toList :: m k v -> [(k, Set v)] Source #
Converts a multimap to a list of key to value-set mappings.
Removing empty sets from the output list does not affect the result:
toList ≡ filter ((/= Set.empty) . snd) . toList
The resulting list can be used to reconstruct the original multimap:
fromList . toList ≡ id
Constructs an empty multimap.
empty ≡ fromList []
lookup :: k -> m k v -> Set v Source #
Returns the set of values associated with a given key.
lookup k (fromList kvs) ≡ foldMap snd (filter ((== k) . fst) kvs)
null :: m k v -> Bool Source #
Indicates whether or not a multimap is empty.
null m ≡ (∀ k. lookup k m == Set.empty)
nonNull :: m k v -> Bool Source #
Indicates whether or not a multimap is non-empty.
nonNull m ≡ (∃ k. lookup k m /= Set.empty)
nonNullKey :: k -> m k v -> Bool Source #
Returns True
iff. the given key is associated with a non-empty set.
nonNullKey k m ≡ (lookup k m /= Set.empty)
nonNullKeys :: m k v -> Set k Source #
Returns the set of keys that are associated with non-empty sets.
all (`nonNullKey` m) (nonNullKeys m)
nonNullCount :: m k v -> Int Source #
Indicates how many keys are associated with non-empty sets.
nonNullCount m ≡ Set.size (nonNullKeys m)
isSubmapOf :: m k v -> m k v -> Bool Source #
Indicates whether or not the first map is a sub-map of the second.
m1 `isSubmapOf` m2 ≡ ∀ k. (lookup k m1 `Set.isSubsetOf` lookup k m2)
update :: k -> Set v -> m k v -> m k v Source #
Updates the set of values associated with a given key.
lookup k1 (update k2 vs m) ≡ if k1 == k2 then vs else lookup k1 m
insert :: k -> Set v -> m k v -> m k v Source #
Inserts values into the set of values associated with a given key.
lookup k1 (insert k2 vs m) ≡ if k1 == k2 then lookup k1 m `Set.union` vs else lookup k1 m
remove :: k -> Set v -> m k v -> m k v Source #
Removes values from the set of values associated with a given key.
lookup k1 (remove k2 vs m) ≡ if k1 == k2 then lookup k1 m `Set.difference` vs else lookup k1 m
union :: m k v -> m k v -> m k v Source #
Computes the union of two multimaps.
Instances must satisfy the following properties:
Idempotence
union m m ≡ m
Identity
union empty m ≡ m union m empty ≡ m
Commutativity
union m1 m2 ≡ union m2 m1
Associativity
union m1 (union m2 m3) ≡ union (union m1 m2) m3
Containment
m1 `isSubmapOf` union m1 m2 m2 `isSubmapOf` union m1 m2
Distributivity
lookup k (union m1 m2) ≡ Set.union (lookup k m1) (lookup k m2)
intersection :: m k v -> m k v -> m k v Source #
Computes the intersection of two multimaps.
Instances must satisfy the following properties:
Idempotence
intersection m m ≡ m
Identity
intersection empty m ≡ empty intersection m empty ≡ empty
Commutativity
intersection m1 m2 ≡ intersection m2 m1
Associativity
intersection m1 (intersection m2 m3) ≡ intersection (intersection m1 m2) m3
Containment
intersection m1 m2 `isSubmapOf` m1 intersection m1 m2 `isSubmapOf` m2
Distributivity
lookup k (intersection m1 m2) ≡ Set.intersection (lookup k m1) (lookup k m2)