Skip to content

Commit f1a53e2

Browse files
authored
Add haddocks for Semigroup and Monoid instances (#190)
* Add minimal docs on Semigroup/Monoid instances * Add additional docs on Semigroup/Monoid instances * Add example documention to 'union' functions * Add example documentation for mappend and (<>)
1 parent f072271 commit f1a53e2

File tree

2 files changed

+52
-0
lines changed

2 files changed

+52
-0
lines changed

Data/HashMap/Base.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -223,11 +223,29 @@ instance Foldable.Foldable (HashMap k) where
223223
#endif
224224

225225
#if __GLASGOW_HASKELL__ >= 711
226+
-- | '<>' = 'union'
227+
--
228+
-- If a key occurs in both maps, the mapping from the first will be the mapping in the result.
229+
--
230+
-- ==== __Examples__
231+
--
232+
-- >>> fromList [(1,'a'),(2,'b')] <> fromList [(2,'c'),(3,'d')]
233+
-- fromList [(1,'a'),(2,'b'),(3,'d')]
226234
instance (Eq k, Hashable k) => Semigroup (HashMap k v) where
227235
(<>) = union
228236
{-# INLINE (<>) #-}
229237
#endif
230238

239+
-- | 'mempty' = 'empty'
240+
--
241+
-- 'mappend' = 'union'
242+
--
243+
-- If a key occurs in both maps, the mapping from the first will be the mapping in the result.
244+
--
245+
-- ==== __Examples__
246+
--
247+
-- >>> mappend (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
248+
-- fromList [(1,'a'),(2,'b'),(3,'d')]
231249
instance (Eq k, Hashable k) => Monoid (HashMap k v) where
232250
mempty = empty
233251
{-# INLINE mempty #-}
@@ -1342,6 +1360,11 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
13421360

13431361
-- | /O(n+m)/ The union of two maps. If a key occurs in both maps, the
13441362
-- mapping from the first will be the mapping in the result.
1363+
--
1364+
-- ==== __Examples__
1365+
--
1366+
-- >>> union (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
1367+
-- fromList [(1,'a'),(2,'b'),(3,'d')]
13451368
union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v
13461369
union = unionWith const
13471370
{-# INLINABLE union #-}

Data/HashSet/Base.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -161,11 +161,35 @@ instance Foldable.Foldable HashSet where
161161
#endif
162162

163163
#if __GLASGOW_HASKELL__ >= 711
164+
-- | '<>' = 'union'
165+
--
166+
-- /O(n+m)/
167+
--
168+
-- To obtain good performance, the smaller set must be presented as
169+
-- the first argument.
170+
--
171+
-- ==== __Examples__
172+
--
173+
-- >>> fromList [1,2] <> fromList [2,3]
174+
-- fromList [1,2,3]
164175
instance (Hashable a, Eq a) => Semigroup (HashSet a) where
165176
(<>) = union
166177
{-# INLINE (<>) #-}
167178
#endif
168179

180+
-- | 'mempty' = 'empty'
181+
--
182+
-- 'mappend' = 'union'
183+
--
184+
-- /O(n+m)/
185+
--
186+
-- To obtain good performance, the smaller set must be presented as
187+
-- the first argument.
188+
--
189+
-- ==== __Examples__
190+
--
191+
-- >>> mappend (fromList [1,2]) (fromList [2,3])
192+
-- fromList [1,2,3]
169193
instance (Hashable a, Eq a) => Monoid (HashSet a) where
170194
mempty = empty
171195
{-# INLINE mempty #-}
@@ -244,6 +268,11 @@ keysSet m = fromMap (() <$ m)
244268
--
245269
-- To obtain good performance, the smaller set must be presented as
246270
-- the first argument.
271+
--
272+
-- ==== __Examples__
273+
--
274+
-- >>> union (fromList [1,2]) (fromList [2,3])
275+
-- fromList [1,2,3]
247276
union :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
248277
union s1 s2 = HashSet $ H.union (asMap s1) (asMap s2)
249278
{-# INLINE union #-}

0 commit comments

Comments
 (0)