@@ -720,23 +720,23 @@ lookupCont ::
720720 -> k
721721 -> Shift
722722 -> HashMap k v -> r
723- lookupCont absent present ! h0 ! k0 ! s0 m0 = go h0 k0 s0 m0
723+ lookupCont absent present ! h0 ! k0 ! s0 m0 = lookupCont_ h0 k0 s0 m0
724724 where
725- go :: Eq k => Hash -> k -> Shift -> HashMap k v -> r
726- go ! _ ! _ ! _ Empty = absent (# # )
727- go h k _ (Leaf hx (L kx x))
725+ lookupCont_ :: Eq k => Hash -> k -> Shift -> HashMap k v -> r
726+ lookupCont_ ! _ ! _ ! _ Empty = absent (# # )
727+ lookupCont_ h k _ (Leaf hx (L kx x))
728728 | h == hx && k == kx = present x (- 1 )
729729 | otherwise = absent (# # )
730- go h k s (BitmapIndexed b v)
730+ lookupCont_ h k s (BitmapIndexed b v)
731731 | b .&. m == 0 = absent (# # )
732732 | otherwise =
733733 case A. index# v (sparseIndex b m) of
734- (# st # ) -> go h k (nextShift s) st
734+ (# st # ) -> lookupCont_ h k (nextShift s) st
735735 where m = mask h s
736- go h k s (Full v) =
736+ lookupCont_ h k s (Full v) =
737737 case A. index# v (index h s) of
738- (# st # ) -> go h k (nextShift s) st
739- go h k _ (Collision hx v)
738+ (# st # ) -> lookupCont_ h k (nextShift s) st
739+ lookupCont_ h k _ (Collision hx v)
740740 | h == hx = lookupInArrayCont absent present k v
741741 | otherwise = absent (# # )
742742{-# INLINE lookupCont #-}
@@ -2713,15 +2713,16 @@ lookupInArrayCont ::
27132713 forall r k v.
27142714#endif
27152715 Eq k => ((# # ) -> r) -> (v -> Int -> r) -> k -> A. Array (Leaf k v) -> r
2716- lookupInArrayCont absent present k0 ary0 = go k0 ary0 0 (A. length ary0)
2716+ lookupInArrayCont absent present k0 ary0 =
2717+ lookupInArrayCont_ k0 ary0 0 (A. length ary0)
27172718 where
2718- go :: Eq k => k -> A. Array (Leaf k v ) -> Int -> Int -> r
2719- go ! k ! ary ! i ! n
2719+ lookupInArrayCont_ :: Eq k => k -> A. Array (Leaf k v ) -> Int -> Int -> r
2720+ lookupInArrayCont_ ! k ! ary ! i ! n
27202721 | i >= n = absent (# # )
27212722 | otherwise = case A. index# ary i of
27222723 (# L kx v # )
27232724 | k == kx -> present v i
2724- | otherwise -> go k ary (i+ 1 ) n
2725+ | otherwise -> lookupInArrayCont_ k ary (i+ 1 ) n
27252726{-# INLINE lookupInArrayCont #-}
27262727
27272728-- | \(O(n)\) Lookup the value associated with the given key in this
0 commit comments