Skip to content

Commit a60a1b2

Browse files
BodigrimShimuuar
authored andcommitted
Hint to GHC that indices are to be used strictly
'basicUnsafe{Read/Write/IndexM}' are class members and, unless a call site was already specialised to a specific vector instance, GHC has no clue that the index is most certainly to be used eagerly. Bang before the index provides this vital for optimizer information.
1 parent 1ca259e commit a60a1b2

File tree

2 files changed

+22
-13
lines changed

2 files changed

+22
-13
lines changed

vector/src/Data/Vector/Generic.hs

Lines changed: 14 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -232,15 +232,20 @@ infixl 9 !
232232
-- | O(1) Indexing.
233233
(!) :: (HasCallStack, Vector v a) => v a -> Int -> a
234234
{-# INLINE_FUSED (!) #-}
235-
(!) v i = checkIndex Bounds i (length v) $ unBox (basicUnsafeIndexM v i)
235+
(!) v !i = checkIndex Bounds i (length v) $ unBox (basicUnsafeIndexM v i)
236+
-- Why do we need ! before i?
237+
-- The reason is that 'basicUnsafeIndexM' is a class member and, unless (!) was
238+
-- already specialised to a specific v, GHC has no clue that i is most certainly
239+
-- to be used eagerly. Bang before i hints this vital for optimizer information.
236240

237241
infixl 9 !?
238242
-- | O(1) Safe indexing.
239243
(!?) :: Vector v a => v a -> Int -> Maybe a
240244
{-# INLINE_FUSED (!?) #-}
241245
-- Use basicUnsafeIndexM @Box to perform the indexing eagerly.
242-
v !? i | i `inRange` length v = case basicUnsafeIndexM v i of Box a -> Just a
243-
| otherwise = Nothing
246+
v !? (!i)
247+
| i `inRange` length v = case basicUnsafeIndexM v i of Box a -> Just a
248+
| otherwise = Nothing
244249

245250

246251
-- | /O(1)/ First element.
@@ -256,7 +261,7 @@ last v = v ! (length v - 1)
256261
-- | /O(1)/ Unsafe indexing without bounds checking.
257262
unsafeIndex :: Vector v a => v a -> Int -> a
258263
{-# INLINE_FUSED unsafeIndex #-}
259-
unsafeIndex v i = checkIndex Unsafe i (length v) $ unBox (basicUnsafeIndexM v i)
264+
unsafeIndex v !i = checkIndex Unsafe i (length v) $ unBox (basicUnsafeIndexM v i)
260265

261266
-- | /O(1)/ First element, without checking if the vector is empty.
262267
unsafeHead :: Vector v a => v a -> a
@@ -316,7 +321,7 @@ unsafeLast v = unsafeIndex v (length v - 1)
316321
-- element) is evaluated eagerly.
317322
indexM :: (HasCallStack, Vector v a, Monad m) => v a -> Int -> m a
318323
{-# INLINE_FUSED indexM #-}
319-
indexM v i = checkIndex Bounds i (length v) $ liftBox $ basicUnsafeIndexM v i
324+
indexM v !i = checkIndex Bounds i (length v) $ liftBox $ basicUnsafeIndexM v i
320325

321326
-- | /O(1)/ First element of a vector in a monad. See 'indexM' for an
322327
-- explanation of why this is useful.
@@ -334,7 +339,7 @@ lastM v = indexM v (length v - 1)
334339
-- explanation of why this is useful.
335340
unsafeIndexM :: (Vector v a, Monad m) => v a -> Int -> m a
336341
{-# INLINE_FUSED unsafeIndexM #-}
337-
unsafeIndexM v i = checkIndex Unsafe i (length v)
342+
unsafeIndexM v !i = checkIndex Unsafe i (length v)
338343
$ liftBox
339344
$ basicUnsafeIndexM v i
340345

@@ -993,7 +998,7 @@ backpermute v is = seq v
993998
-- NOTE: we do it this way to avoid triggering LiberateCase on n in
994999
-- polymorphic code
9951000
index :: HasCallStack => Int -> Box a
996-
index i = checkIndex Bounds i n $ basicUnsafeIndexM v i
1001+
index !i = checkIndex Bounds i n $ basicUnsafeIndexM v i
9971002

9981003
-- | Same as 'backpermute', but without bounds checking.
9991004
unsafeBackpermute :: (Vector v a, Vector v Int) => v a -> v Int -> v a
@@ -1010,7 +1015,7 @@ unsafeBackpermute v is = seq v
10101015
{-# INLINE index #-}
10111016
-- NOTE: we do it this way to avoid triggering LiberateCase on n in
10121017
-- polymorphic code
1013-
index i = checkIndex Unsafe i n $ basicUnsafeIndexM v i
1018+
index !i = checkIndex Unsafe i n $ basicUnsafeIndexM v i
10141019

10151020
-- Safe destructive updates
10161021
-- ------------------------
@@ -2534,7 +2539,7 @@ streamR v = v `seq` n `seq` (Bundle.unfoldr get n `Bundle.sized` Exact n)
25342539

25352540
{-# INLINE get #-}
25362541
get 0 = Nothing
2537-
get i = let i' = i-1
2542+
get i = let !i' = i-1
25382543
in
25392544
case basicUnsafeIndexM v i' of Box x -> Just (x, i')
25402545

vector/src/Data/Vector/Generic/Mutable.hs

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -700,21 +700,25 @@ exchange v i x = checkIndex Bounds i (length v) $ unsafeExchange v i x
700700
-- | Yield the element at the given position. No bounds checks are performed.
701701
unsafeRead :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m a
702702
{-# INLINE unsafeRead #-}
703-
unsafeRead v i = checkIndex Unsafe i (length v)
703+
unsafeRead v !i = checkIndex Unsafe i (length v)
704704
$ stToPrim
705705
$ basicUnsafeRead v i
706+
-- Why do we need ! before i?
707+
-- The reason is that 'basicUnsafeRead' is a class member and, unless 'unsafeRead' was
708+
-- already specialised to a specific v, GHC has no clue that i is most certainly
709+
-- to be used eagerly. Bang before i hints this vital for optimizer information.
706710

707711
-- | Replace the element at the given position. No bounds checks are performed.
708712
unsafeWrite :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> a -> m ()
709713
{-# INLINE unsafeWrite #-}
710-
unsafeWrite v i x = checkIndex Unsafe i (length v)
714+
unsafeWrite v !i x = checkIndex Unsafe i (length v)
711715
$ stToPrim
712716
$ basicUnsafeWrite v i x
713717

714718
-- | Modify the element at the given position. No bounds checks are performed.
715719
unsafeModify :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (a -> a) -> Int -> m ()
716720
{-# INLINE unsafeModify #-}
717-
unsafeModify v f i = checkIndex Unsafe i (length v)
721+
unsafeModify v f !i = checkIndex Unsafe i (length v)
718722
$ stToPrim
719723
$ basicUnsafeRead v i >>= \x ->
720724
basicUnsafeWrite v i (f x)
@@ -725,7 +729,7 @@ unsafeModify v f i = checkIndex Unsafe i (length v)
725729
-- @since 0.12.3.0
726730
unsafeModifyM :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (a -> m a) -> Int -> m ()
727731
{-# INLINE unsafeModifyM #-}
728-
unsafeModifyM v f i = checkIndex Unsafe i (length v)
732+
unsafeModifyM v f !i = checkIndex Unsafe i (length v)
729733
$ stToPrim . basicUnsafeWrite v i =<< f =<< stToPrim (basicUnsafeRead v i)
730734

731735
-- | Swap the elements at the given positions. No bounds checks are performed.

0 commit comments

Comments
 (0)