[GHC] #15728: Program with safe array operations triggers debug runtime assertion

#15728: Program with safe array operations triggers debug runtime assertion
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Runtime | Version: 8.6.1
System |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I'll try to minimize later.
Main.hs:
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
import Control.Monad
import Control.Monad.ST
import Data.Primitive.Array
import Data.Primitive.ByteArray
import Data.Primitive.SmallArray
import System.Environment
import System.Mem
import Foreign.C
data A arr = A !Int arr
enumSmallArray :: Int -> A (SmallArray Int)
enumSmallArray n = runST $ do
arr <- newSmallArray n 0
forM_ [1..n] $ \i ->
writeSmallArray arr i i
iarr <- freezeSmallArray arr 0 n
return (A n iarr)
consumeSmallArray :: A (SmallArray a) -> a
consumeSmallArray (A n arr) = indexSmallArray arr (n - 1)
enumArray :: Int -> A (Array Int)
enumArray n = runST $ do
arr <- newArray n 0
forM_ [1..n] $ \i ->
writeArray arr i i
iarr <- freezeArray arr 0 n
return (A n iarr)
consumeArray :: A (Array a) -> a
consumeArray (A n arr) = indexArray arr (n - 1)
foreign import ccall "printInt"
printInt :: CInt -> IO ()
main :: IO ()
main = do
n <- (\[s] -> read s) <$> getArgs
ints <- forM [1..n] $ \i -> do
let x = consumeSmallArray (enumSmallArray 12)
y = consumeArray (enumArray i)
case x+y of
r -> when (i `mod` 5000 == 0) performMajorGC
>> return r
printInt (fromIntegral (sum ints))
}}}
print.c:
{{{
#include

bt #0 __GI_raise (sig=sig@entry=6) at ../sysdeps/unix/sysv/linux/raise.c:51 #1 0x00007ffff6e18dc1 in __GI_abort () at abort.c:79 #2 0x0000000000898c87 in rtsFatalInternalErrorFn (s=0x8fdf18 "ASSERTION FAILED: file %s, line %u\n", ap=0x7fffffff83a8) at rts/RtsMessages.c:186 #3 0x0000000000898871 in barf (s=0x8fdf18 "ASSERTION FAILED: file %s,
#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The backtrace is, {{{ line %u\n") at rts/RtsMessages.c:48 #4 0x00000000008988d9 in _assertFail (filename=0x900a72 "rts/sm/Storage.c", linenum=978) at rts/RtsMessages.c:63 #5 0x00000000008a0d6e in allocateMightFail (cap=0xc92500 <MainCapability>, n=14) at rts/sm/Storage.c:978 #6 0x00000000008a09eb in allocate (cap=0xc92500 <MainCapability>, n=14) at rts/sm/Storage.c:853 #7 0x00000000008c51ad in stg_freezzeSmallArrayzh () at rts/PrimOps.cmm:462 Backtrace stopped: previous frame inner to this frame (corrupt stack?) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The assertion in question expects to see that the bits that we are about to return to the caller have been cleared with `0xaa` (since sanity checking is enabled). However, isn't quite the case, {{{ #5 0x00000000008a0d6e in allocateMightFail (cap=0xc92500 <MainCapability>, n=14) at rts/sm/Storage.c:978 978 IF_DEBUG(sanity, ASSERT(*((StgWord8*)p) == 0xaa));
x/8a p 0x4200105788: 0x420008da21 0xaaaaaaaaaaaaaaaa 0x4200105798: 0xaaaaaaaaaaaaaaaa 0xaaaaaaaaaaaaaaaa 0x42001057a8: 0xaaaaaaaaaaaaaaaa 0xaaaaaaaaaaaaaaaa 0x42001057b8: 0xaaaaaaaaaaaaaaaa 0xaaaaaaaaaaaaaaaa }}}
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It appears that the write in question comes from code emitted for `writeSmallArray#`: {{{ Hardware watchpoint 1: *(void**) 0x4200105788 Old value = (void *) 0xaaaaaaaaaaaaaaaa New value = (void *) 0x4200012f01 0x000000000041fb51 in .Lslgf_info () at primitive/Data/Primitive/SmallArray.hs:191 191 primitive_ $ writeSmallArray# sma# i# x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => highest Comment: Bumping the priority of this since it looks to me like this could result in corruption. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => invalid Comment: Sigh. The problem was staring at me the entire time: the testcase is wrong. Specifically: {{{#!hs arr <- newSmallArray n 0 forM_ [1..n] $ \i -> writeSmallArray arr i i }}} `[1..n]` will produce an out-of-bounds index for the allocated array. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): So why don't we get an array-bounds check? Or is there no check? In which case it should be `unsafeWriteSmallArray`! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15728: Program with safe array operations triggers debug runtime assertion -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: Component: Runtime System | Version: 8.6.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): That's because the `primitive` library is a very thin wrapper around GHC primops, and GHC primops (`readArray#` etc.) don't do bounds checking. FWIW I just opened a ticket: https://github.com/haskell/primitive/issues/212 at the very least we should mention this in primitive's haddocks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15728#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC