X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FArr.lhs;h=1b2f0bb543da79b6bb50b1a0727593544732ba38;hb=2cf27b8981aec980350a291b90499916f1fbc8af;hp=e462617c653620b2a3865fdc7b33a09a4f2a9817;hpb=c887ba0e9f763eef178ff01604000143347c9f32;p=ghc-base.git diff --git a/GHC/Arr.lhs b/GHC/Arr.lhs index e462617..1b2f0bb 100644 --- a/GHC/Arr.lhs +++ b/GHC/Arr.lhs @@ -80,6 +80,7 @@ class (Ord a) => Ix a where -- 'index' is typically over-ridden in instances, with essentially -- the same code, but using indexError instead of hopelessIndexError -- Reason: we have 'Show' at the instances + {-# INLINE index #-} -- See Note [Inlining index] index b i | inRange b i = unsafeIndex b i | otherwise = hopelessIndexError @@ -110,8 +111,54 @@ hence is empty %* * %********************************************************* +Note [Inlining index] +~~~~~~~~~~~~~~~~~~~~~ +We inline the 'index' operation, + + * Partly because it generates much faster code + (although bigger); see Trac #1216 + + * Partly because it exposes the bounds checks to the simplifier which + might help a big. + +If you make a per-instance index method, you may consider inlining it. + +Note [Double bounds-checking of index values] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When you index an array, a!x, there are two possible bounds checks we might make: + + (A) Check that (inRange (bounds a) x) holds. + + (A) is checked in the method for 'index' + + (B) Check that (index (bounds a) x) lies in the range 0..n, + where n is the size of the underlying array + + (B) is checked in the top-level function (!), in safeIndex. + +Of course it *should* be the case that (A) holds iff (B) holds, but that +is a property of the particular instances of index, bounds, and inRange, +so GHC cannot guarantee it. + + * If you do (A) and not (B), then you might get a seg-fault, + by indexing at some bizarre location. Trac #1610 + + * If you do (B) but not (A), you may get no complaint when you index + an array out of its semantic bounds. Trac #2120 + +At various times we have had (A) and not (B), or (B) and not (A); both +led to complaints. So now we implement *both* checks (Trac #2669). + +For 1-d, 2-d, and 3-d arrays of Int we have specialised instances to avoid this. + +Note [Out-of-bounds error messages] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The default method for 'index' generates hoplelessIndexError, because +Ix doesn't have Show as a superclass. For particular base types we +can do better, so we override the default method for index. + \begin{code} --- abstract these errors from the relevant index functions so that +-- Abstract these errors from the relevant index functions so that -- the guts of the function will be small enough to inline. {-# NOINLINE indexError #-} @@ -133,6 +180,8 @@ instance Ix Char where {-# INLINE unsafeIndex #-} unsafeIndex (m,_n) i = fromEnum i - fromEnum m + {-# INLINE index #-} -- See Note [Out-of-bounds error messages] + -- and Note [Inlining index] index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Char" @@ -148,6 +197,8 @@ instance Ix Int where {-# INLINE unsafeIndex #-} unsafeIndex (m,_n) i = i - m + {-# INLINE index #-} -- See Note [Out-of-bounds error messages] + -- and Note [Inlining index] index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Int" @@ -162,6 +213,8 @@ instance Ix Integer where {-# INLINE unsafeIndex #-} unsafeIndex (m,_n) i = fromInteger (i - m) + {-# INLINE index #-} -- See Note [Out-of-bounds error messages] + -- and Note [Inlining index] index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Integer" @@ -175,6 +228,8 @@ instance Ix Bool where -- as derived {-# INLINE unsafeIndex #-} unsafeIndex (l,_) i = fromEnum i - fromEnum l + {-# INLINE index #-} -- See Note [Out-of-bounds error messages] + -- and Note [Inlining index] index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Bool" @@ -188,6 +243,8 @@ instance Ix Ordering where -- as derived {-# INLINE unsafeIndex #-} unsafeIndex (l,_) i = fromEnum i - fromEnum l + {-# INLINE index #-} -- See Note [Out-of-bounds error messages] + -- and Note [Inlining index] index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Ordering" @@ -201,7 +258,8 @@ instance Ix () where unsafeIndex ((), ()) () = 0 {-# INLINE inRange #-} inRange ((), ()) () = True - {-# INLINE index #-} + + {-# INLINE index #-} -- See Note [Inlining index] index b i = unsafeIndex b i ---------------------------------------------------------------------- @@ -296,7 +354,6 @@ type IPr = (Int, Int) -- | The type of immutable non-strict (boxed) arrays -- with indices in @i@ and elements in @e@. --- The Int is the number of elements in the Array. data Ix i => Array i e = Array !i -- the lower bound, l !i -- the upper bound, u @@ -445,13 +502,27 @@ safeRangeSize (l,u) = let r = rangeSize (l, u) negRange :: Int -- Uninformative, but Ix does not provide Show negRange = error "Negative range size" -{-# INLINE safeIndex #-} +{-# INLINE[1] safeIndex #-} +-- See Note [Double bounds-checking of index values] +-- Inline *after* (!) so the rules can fire 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 +-- See Note [Double bounds-checking of index values] +{-# RULES +"safeIndex/I" safeIndex = lessSafeIndex :: (Int,Int) -> Int -> Int -> Int +"safeIndex/(I,I)" safeIndex = lessSafeIndex :: ((Int,Int),(Int,Int)) -> Int -> (Int,Int) -> Int +"safeIndex/(I,I,I)" safeIndex = lessSafeIndex :: ((Int,Int,Int),(Int,Int,Int)) -> Int -> (Int,Int,Int) -> Int + #-} + +lessSafeIndex :: Ix i => (i, i) -> Int -> i -> Int +-- See Note [Double bounds-checking of index values] +-- Do only (A), the semantic check +lessSafeIndex (l,u) _ i = index (l,u) i + -- Don't inline this long error message everywhere!! badSafeIndex :: Int -> Int -> Int badSafeIndex i' n = error ("Error in array index; " ++ show i' ++ @@ -489,7 +560,7 @@ assocs :: Ix i => Array i e -> [(i, e)] assocs arr@(Array l u _ _) = [(i, arr ! i) | i <- range (l,u)] --- | The 'accumArray' deals with repeated indices in the association +-- | The 'accumArray' function deals with repeated indices in the association -- list using an /accumulating function/ which combines the values of -- associations with the same index. -- For example, given a list of values of some index type, @hist@