[GHC] #14912: UnsafeReenter test fails with threaded1 and threaded2

#14912: UnsafeReenter test fails with threaded1 and threaded2 --------------------------------------+--------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- {{{ /tmp/ghctest-n4fi8zlk/test spaces/./ffi/should_fail/UnsafeReenter.run UnsafeReenter [bad exit code] (threaded1) /tmp/ghctest-n4fi8zlk/test spaces/./ffi/should_fail/UnsafeReenter.run UnsafeReenter [bad exit code] (threaded2) }}} It's a quite simple program: {{{#!hs {-# LANGUAGE ForeignFunctionInterface #-} -- | Test that unsafe FFI calls crash the RTS if they attempt to re-enter -- Haskell-land module Main where import Foreign foreign import ccall "wrapper" wrap_f :: IO () -> IO (FunPtr (IO ())) foreign import ccall unsafe hello :: FunPtr (IO ()) -> IO () f :: IO () f = putStrLn "Back in Haskell" main :: IO () main = do putStrLn "In Haskell" wrap_f f >>= hello putStrLn "Finished" }}} This just seem to hang (until timeout) with the `threaded1` and `threaded2` ways, instead of erroring out with: {{{ UnsafeReenter: schedule: re-entered unsafely. Perhaps a 'foreign import unsafe' should be 'safe'? }}} which is the expected behaviour. I'll mark the test broken for those 2 ways in an upcoming patch, but this probably deserves a new ticket, so here it is. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14912 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14912: UnsafeReenter test fails with threaded1 and threaded2 -----------------------------------+-------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Comment (by alpmestan): I'm now seeing it hang with the `profthreaded` way as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14912#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14912: UnsafeReenter test fails with threaded1 and threaded2 -----------------------------------+-------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14743 | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Changes (by osa1): * cc: simonmar (added) * related: => #14743 Comment: This still happens with GHC HEAD, but only with threaded runtime. {{{ $ ghc-stage2 UnsafeReenter.hs UnsafeReenterC.c -fforce-recomp -threaded [1 of 1] Compiling Main ( UnsafeReenter.hs, UnsafeReenter.o ) Linking UnsafeReenter ... $ ./UnsafeReenter In Haskell in C ^C^C }}} Interestingly, if I add `-N2` the program terminates, but not with the error message as expected! {{{ $ ./UnsafeReenter +RTS -N2 In Haskell in C Back in Haskell Finished }}} I checked Haskell 2010 and this program actually has an undefined behavior: (section 8.4.3)
safe call is less efficient, but guarantees to leave the Haskell system in a state that allows callbacks from the external code. In contrast, an unsafe call, while carrying less overhead, must not trigger a callback into the Haskell system. If it does, the system behaviour is undefined.
So both outputs above are actually fine. But perhaps we still want to catch Haskell calls from unsafe FFI calls in the current implementation? Simon, any ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14912#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14912: UnsafeReenter test fails with threaded1 and threaded2 -----------------------------------+-------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14743 | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Comment (by simonmar): This will only fail for the non-threaded runtime, because the threaded RTS will hang trying to acquire the same capability that the thread already holds. Let's just omit the threaded ways for this test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14912#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14912: UnsafeReenter test fails with threaded1 and threaded2 -----------------------------------+-------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14743 | Differential Rev(s): Phab:D5136 Wiki Page: | -----------------------------------+-------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D5136 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14912#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14912: UnsafeReenter test fails with threaded1 and threaded2
-----------------------------------+--------------------------------------
Reporter: alpmestan | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Runtime System | Version: 8.5
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #14743 | Differential Rev(s): Phab:D5136
Wiki Page: |
-----------------------------------+--------------------------------------
Comment (by Ömer Sinan Ağacan

#14912: UnsafeReenter test fails with threaded1 and threaded2 -----------------------------------+-------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14743 | Differential Rev(s): Phab:D5136 Wiki Page: | -----------------------------------+-------------------------------------- Changes (by osa1): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14912#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC