[GHC] #14346: 8.2.1 regression: heap corruption after safe foreign calls

GHC ghc-devs at haskell.org
Thu Oct 12 09:26:57 UTC 2017


#14346: 8.2.1 regression: heap corruption after safe foreign calls
-------------------------------------+-------------------------------------
           Reporter:  andrewchen     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  highest        |         Milestone:
          Component:  Runtime        |           Version:  8.2.1
  System                             |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Runtime crash
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Test case: (compile with ghc 8.2.1 and -threaded option)
 {{{#!haskell
 module Main where

 import Control.Concurrent
 import Control.Monad
 import Data.Word
 import Foreign.Marshal.Alloc
 import Foreign.Ptr
 import Foreign.Storable

 foreign import ccall safe "test"
     c_test :: Ptr Word32 -> IO ()

 main :: IO ()
 main = do
     replicateM_ 1000 $ threadDelay 1000
     _ <- forkIO $ forever $ threadDelay 100
     allocaBytes 4 $ \p -> forever $ do
         c_test p
         x <- peek p
         unless (x == 0xDEADBEEF) $ putStrLn "value mismatch"
 }}}
 {{{#!c
 void test(unsigned int *buf) {
     *buf = 0xDEADBEEF;
 }
 }}}

 On my machine, it detects a few value mismatches before crashing with
 sigsegv.
 {{{
 $ time ./.stack-work/install/x86_64-linux-
 nopie/nightly-2017-10-10/8.2.1/bin/bug
 value mismatch
 value mismatch
 value mismatch
 value mismatch
 zsh: segmentation fault (core dumped)  ./.stack-work/install/x86_64-linux-
 nopie/nightly-2017-10-10/8.2.1/bin/bug
 ./.stack-work/install/x86_64-linux-nopie/nightly-2017-10-10/8.2.1/bin/bug
 2.11s user 0.25s system 66% cpu 3.543 total
 }}}

 I believe this is what is causing crashes in xmobar. See discussion:
 https://github.com/jaor/xmobar/issues/310. Note that the crash in xmobar
 still happens without -threaded option, while this example only breaks
 when compiled with -threaded.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14346>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list