@@ -488,7 +488,7 @@ cmp cmpk cmpv t1 t2 = go (leavesAndCollisions t1 []) (leavesAndCollisions t2 [])
488488
489489 leafCompare (L k v) (L k' v') = cmpk k k' `mappend` cmpv v v'
490490
491- -- Same as 'equal2' but doesn't compare the values.
491+ -- | Same as 'equal2' but doesn't compare the values.
492492equalKeys1 :: (k -> k' -> Bool ) -> HashMap k v -> HashMap k' v' -> Bool
493493equalKeys1 eq t1 t2 = go (leavesAndCollisions t1 [] ) (leavesAndCollisions t2 [] )
494494 where
@@ -504,7 +504,7 @@ equalKeys1 eq t1 t2 = go (leavesAndCollisions t1 []) (leavesAndCollisions t2 [])
504504
505505 leafEq (L k _) (L k' _) = eq k k'
506506
507- -- Same as 'equal1' but doesn't compare the values.
507+ -- | Same as 'equal1' but doesn't compare the values.
508508equalKeys :: Eq k => HashMap k v -> HashMap k v' -> Bool
509509equalKeys = go
510510 where
@@ -650,7 +650,7 @@ lookup' h k m = case lookupRecordCollision# h k m of
650650 (# | (# a, _i # ) # ) -> Just a
651651{-# INLINE lookup' #-}
652652
653- -- The result of a lookup, keeping track of if a hash collision occurred.
653+ -- | The result of a lookup, keeping track of if a hash collision occurred.
654654-- If a collision did not occur then it will have the Int value (-1).
655655data LookupRes a = Absent | Present a ! Int
656656
@@ -659,7 +659,7 @@ lookupResToMaybe Absent = Nothing
659659lookupResToMaybe (Present x _) = Just x
660660{-# INLINE lookupResToMaybe #-}
661661
662- -- Internal helper for lookup. This version takes the precomputed hash so
662+ -- | Internal helper for lookup. This version takes the precomputed hash so
663663-- that functions that make multiple calls to lookup and related functions
664664-- (insert, delete) only need to calculate the hash once.
665665--
@@ -678,7 +678,7 @@ lookupRecordCollision h k m = case lookupRecordCollision# h k m of
678678 (# | (# a, i # ) # ) -> Present a (I # i) -- GHC will eliminate the I#
679679{-# INLINE lookupRecordCollision #-}
680680
681- -- Why do we produce an Int# instead of an Int? Unfortunately, GHC is not
681+ -- | Why do we produce an Int# instead of an Int? Unfortunately, GHC is not
682682-- yet any good at unboxing things *inside* products, let alone sums. That
683683-- may be changing in GHC 8.6 or so (there is some work in progress), but
684684-- for now we use Int# explicitly here. We don't need to push the Int#
@@ -689,7 +689,7 @@ lookupRecordCollision# h k m =
689689-- INLINABLE to specialize to the Eq instance.
690690{-# INLINABLE lookupRecordCollision# #-}
691691
692- -- A two-continuation version of lookupRecordCollision. This lets us
692+ -- | A two-continuation version of lookupRecordCollision. This lets us
693693-- share source code between lookup and lookupRecordCollision without
694694-- risking any performance degradation.
695695--
@@ -835,7 +835,7 @@ insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0
835835 | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
836836{-# INLINABLE insert' #-}
837837
838- -- Insert optimized for the case when we know the key is not in the map.
838+ -- | Insert optimized for the case when we know the key is not in the map.
839839--
840840-- It is only valid to call this when the key does not exist in the map.
841841--
@@ -871,7 +871,7 @@ insertNewKey !h0 !k0 x0 !m0 = go h0 k0 x0 0 m0
871871{-# NOINLINE insertNewKey #-}
872872
873873
874- -- Insert optimized for the case when we know the key is in the map.
874+ -- | Insert optimized for the case when we know the key is in the map.
875875--
876876-- It is only valid to call this when the key exists in the map and you know the
877877-- hash collision position if there was one. This information can be obtained
@@ -913,7 +913,7 @@ insertKeyExists !collPos0 !h0 !k0 x0 !m0 = go collPos0 h0 k0 x0 m0
913913
914914{-# NOINLINE insertKeyExists #-}
915915
916- -- Replace the ith Leaf with Leaf k v.
916+ -- | Replace the ith Leaf with Leaf k v.
917917--
918918-- This does not check that @i@ is within bounds of the array.
919919setAtPosition :: Int -> k -> v -> A. Array (Leaf k v ) -> A. Array (Leaf k v )
@@ -1053,7 +1053,7 @@ insertModifying x f k0 m0 = go h0 k0 0 m0
10531053 | otherwise = go h k s $ BitmapIndexed (mask hy s) (A. singleton t)
10541054{-# INLINABLE insertModifying #-}
10551055
1056- -- Like insertModifying for arrays; used to implement insertModifying
1056+ -- | Like insertModifying for arrays; used to implement insertModifying
10571057insertModifyingArr :: Eq k => v -> (v -> (# v # )) -> k -> A. Array (Leaf k v )
10581058 -> A. Array (Leaf k v )
10591059insertModifyingArr x f k0 ary0 = go k0 ary0 0 (A. length ary0)
@@ -1341,12 +1341,12 @@ alterF f = \ !k !m ->
13411341-- rule from firing.
13421342{-# INLINABLE [0] alterF #-}
13431343
1344- -- This is just a bottom value. See the comment on the "alterFWeird"
1344+ -- | This is just a bottom value. See the comment on the "alterFWeird"
13451345-- rule.
13461346test_bottom :: a
13471347test_bottom = error " Data.HashMap.alterF internal error: hit test_bottom"
13481348
1349- -- We use this as an error result in RULES to ensure we don't get
1349+ -- | We use this as an error result in RULES to ensure we don't get
13501350-- any useless CallStack nonsense.
13511351bogus# :: (# # ) -> (# a # )
13521352bogus# _ = error " Data.HashMap.alterF internal error: hit bogus#"
@@ -1403,7 +1403,7 @@ bogus# _ = error "Data.HashMap.alterF internal error: hit bogus#"
14031403 alterFWeird _ign1 _ign2 f = \ !k !m -> Const (getConst (f (lookup k m)))
14041404 #-}
14051405
1406- -- This is a very unsafe version of alterF used for RULES. When calling
1406+ -- | This is a very unsafe version of alterF used for RULES. When calling
14071407-- alterFWeird x y f, the following *must* hold:
14081408--
14091409-- x = f Nothing
0 commit comments