@@ -606,18 +606,35 @@ fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty
606606{-# INLINABLE fromList #-}
607607
608608-- | /O(n*log n)/ Construct a map from a list of elements. Uses
609- -- the provided function f to merge duplicate entries (f newVal oldVal).
609+ -- the provided function @f@ to merge duplicate entries with
610+ -- @(f newVal oldVal)@.
610611--
611- -- For example:
612+ -- === Examples
612613--
613- -- > fromListWith (+) [ (x, 1) | x <- xs ]
614+ -- Given a list @xs@, create a map with the number of occurrences of each
615+ -- element in @xs@:
614616--
615- -- will create a map with number of occurrences of each element in xs.
617+ -- > let xs = ['a', 'b', 'a']
618+ -- > in fromListWith (+) [ (x, 1) | x <- xs ]
619+ -- >
620+ -- > = fromList [('a', 2), ('b', 1)]
616621--
617- -- > fromListWith (++) [ (k, [v]) | (k, v) <- xs ]
622+ -- Given a list of key-value pairs @xs :: [(k, v)]@, group all values by their
623+ -- keys and return a @HashMap k [v]@.
618624--
619- -- will group all values by their keys in a list 'xs :: [(k, v)]' and
620- -- return a 'HashMap k [v]'.
625+ -- > let xs = ('a', 1), ('b', 2), ('a', 3)]
626+ -- > in fromListWith (++) [ (k, [v]) | (k, v) <- xs ]
627+ -- >
628+ -- > = fromList [('a', [3, 1]), ('b', [2])]
629+ --
630+ -- Note that the lists in the resulting map contain elements in reverse order
631+ -- from their occurences in the original list.
632+ --
633+ -- More generally, duplicate entries are accumulated as follows;
634+ -- this matters when @f@ is not commutative or not associative.
635+ --
636+ -- > fromListWith f [(k, a), (k, b), (k, c), (k, d)]
637+ -- > = fromList [(k, f d (f c (f b a)))]
621638fromListWith :: (Eq k , Hashable k ) => (v -> v -> v ) -> [(k , v )] -> HashMap k v
622639fromListWith f = L. foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty
623640{-# INLINE fromListWith #-}
0 commit comments