[commit: ghc] master: Make absolutely sure that 'done' and 'safeIndex' are strict in the index (68a1e67)

git at git.haskell.org git at git.haskell.org
Thu Apr 24 07:43:54 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/68a1e679f0b97db99c552c3dbf69e651291826fa/ghc

>---------------------------------------------------------------

commit 68a1e679f0b97db99c552c3dbf69e651291826fa
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Apr 22 14:40:12 2014 +0100

    Make absolutely sure that 'done' and 'safeIndex' are strict in the index
    
    This is just to make sure that there is no redundant boxing.
    For safeIndex, for example, the error path doesn't evaluate the
    index, so it may be passed boxed unless safeIndex is inlined bodily,
    which I don't want to rely on.


>---------------------------------------------------------------

68a1e679f0b97db99c552c3dbf69e651291826fa
 libraries/base/GHC/Arr.lhs |   13 ++++++++-----
 1 file changed, 8 insertions(+), 5 deletions(-)

diff --git a/libraries/base/GHC/Arr.lhs b/libraries/base/GHC/Arr.lhs
index 6d11e38..14bc917 100644
--- a/libraries/base/GHC/Arr.lhs
+++ b/libraries/base/GHC/Arr.lhs
@@ -491,7 +491,8 @@ fill marr# (I# i#, e) next
 {-# INLINE done #-}
 done :: Ix i => i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)
 -- See NB on 'fill'
-done l u n marr#
+-- Make sure it is strict in 'n'
+done l u n@(I# _) marr#
   = \s1# -> case unsafeFreezeArray# marr# s1# of
               (# s2#, arr# #) -> (# s2#, Array l u n arr# #)
 
@@ -534,11 +535,13 @@ negRange = error "Negative range size"
 {-# INLINE[1] safeIndex #-}
 -- See Note [Double bounds-checking of index values]
 -- Inline *after* (!) so the rules can fire
+-- Make sure it is strict in n
 safeIndex :: Ix i => (i, i) -> Int -> i -> Int
-safeIndex (l,u) n i = let i' = index (l,u) i
-                      in if (0 <= i') && (i' < n)
-                         then i'
-                         else badSafeIndex i' n
+safeIndex (l,u) n@(I# _) i 
+  | (0 <= i') && (i' < n) = i'
+  | otherwise             = badSafeIndex i' n
+  where
+    i' = index (l,u) i
 
 -- See Note [Double bounds-checking of index values]
 {-# RULES



More information about the ghc-commits mailing list