Skip to content

Commit 96ee359

Browse files
committed
Add NOTE like one used by GHC
We have longish comment which is referenced from multiple places in source code. GHC notes seems good option for that
1 parent 49d27c0 commit 96ee359

File tree

2 files changed

+22
-8
lines changed

2 files changed

+22
-8
lines changed

vector/src/Data/Vector/Generic.hs

Lines changed: 17 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -228,20 +228,31 @@ null = Bundle.null . stream
228228
-- Indexing
229229
-- --------
230230

231+
-- NOTE: [Strict indexing]
232+
-- ~~~~~~~~~~~~~~~~~~~~~~~
233+
--
234+
-- Why index parameters are strict in indexing ((!), (!?)) functions
235+
-- and functions for accessing elements in mutable arrays ('unsafeRead',
236+
-- 'unsafeWrite', 'unsafeModify'), and slice functions?
237+
--
238+
-- These function call class methods ('basicUnsafeIndexM',
239+
-- 'basicUnsafeRead', etc) and, unless (!) was already specialised to
240+
-- a specific v, GHC has no clue that i is most certainly to be used
241+
-- eagerly. Bang before i hints this vital for optimizer information.
242+
243+
231244
infixl 9 !
232245
-- | O(1) Indexing.
233246
(!) :: (HasCallStack, Vector v a) => v a -> Int -> a
234247
{-# INLINE_FUSED (!) #-}
248+
-- See NOTE: [Strict indexing]
235249
(!) 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.
240250

241251
infixl 9 !?
242252
-- | O(1) Safe indexing.
243253
(!?) :: Vector v a => v a -> Int -> Maybe a
244254
{-# INLINE_FUSED (!?) #-}
255+
-- See NOTE: [Strict indexing]
245256
-- Use basicUnsafeIndexM @Box to perform the indexing eagerly.
246257
v !? (!i)
247258
| i `inRange` length v = case basicUnsafeIndexM v i of Box a -> Just a
@@ -261,6 +272,7 @@ last v = v ! (length v - 1)
261272
-- | /O(1)/ Unsafe indexing without bounds checking.
262273
unsafeIndex :: Vector v a => v a -> Int -> a
263274
{-# INLINE_FUSED unsafeIndex #-}
275+
-- See NOTE: [Strict indexing]
264276
unsafeIndex v !i = checkIndex Unsafe i (length v) $ unBox (basicUnsafeIndexM v i)
265277

266278
-- | /O(1)/ First element, without checking if the vector is empty.
@@ -457,6 +469,7 @@ unsafeSlice :: Vector v a => Int -- ^ @i@ starting index
457469
-> v a
458470
-> v a
459471
{-# INLINE_FUSED unsafeSlice #-}
472+
-- See NOTE: [Strict indexing]
460473
unsafeSlice !i !n v = checkSlice Unsafe i n (length v) $ basicUnsafeSlice i n v
461474

462475
-- | /O(1)/ Yield all but the last element without copying. The vector may not

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

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -425,6 +425,7 @@ unsafeSlice :: MVector v a => Int -- ^ starting index
425425
-> v s a
426426
-> v s a
427427
{-# INLINE unsafeSlice #-}
428+
-- See NOTE: [Strict indexing] in D.V.Generic
428429
unsafeSlice !i !n v = checkSlice Unsafe i n (length v)
429430
$ basicUnsafeSlice i n v
430431

@@ -700,24 +701,23 @@ exchange v i x = checkIndex Bounds i (length v) $ unsafeExchange v i x
700701
-- | Yield the element at the given position. No bounds checks are performed.
701702
unsafeRead :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m a
702703
{-# INLINE unsafeRead #-}
704+
-- See NOTE: [Strict indexing] in D.V.Generic
703705
unsafeRead v !i = checkIndex Unsafe i (length v)
704706
$ stToPrim
705707
$ 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.
710708

711709
-- | Replace the element at the given position. No bounds checks are performed.
712710
unsafeWrite :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> a -> m ()
713711
{-# INLINE unsafeWrite #-}
712+
-- See NOTE: [Strict indexing] in D.V.Generic
714713
unsafeWrite v !i x = checkIndex Unsafe i (length v)
715714
$ stToPrim
716715
$ basicUnsafeWrite v i x
717716

718717
-- | Modify the element at the given position. No bounds checks are performed.
719718
unsafeModify :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (a -> a) -> Int -> m ()
720719
{-# INLINE unsafeModify #-}
720+
-- See NOTE: [Strict indexing] in D.V.Generic
721721
unsafeModify v f !i = checkIndex Unsafe i (length v)
722722
$ stToPrim
723723
$ basicUnsafeRead v i >>= \x ->
@@ -729,6 +729,7 @@ unsafeModify v f !i = checkIndex Unsafe i (length v)
729729
-- @since 0.12.3.0
730730
unsafeModifyM :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (a -> m a) -> Int -> m ()
731731
{-# INLINE unsafeModifyM #-}
732+
-- See NOTE: [Strict indexing] in D.V.Generic
732733
unsafeModifyM v f !i = checkIndex Unsafe i (length v)
733734
$ stToPrim . basicUnsafeWrite v i =<< f =<< stToPrim (basicUnsafeRead v i)
734735

0 commit comments

Comments
 (0)