[GHC] #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException ----------------------------------------+------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Keywords: | Operating System: MacOS X Architecture: Unknown/Multiple | Type of failure: GHCi crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+------------------------------- I tried running some `GLUT` code in macOS Sierra (Version 10.12.5 (16F73)) and ran into a strange error. If you're willing to use `cabal-install`, you can just do this: {{{ $ cabal install GLFW-0.5.2.5 }}} And run this module in with `runghc`: {{{#!hs -- GLUT.hs module Main where import Graphics.UI.GLUT (($=), getArgsAndInitialize, createWindow, displayCallback, mainLoop) main :: IO () main = do (_progName, _args) <- getArgsAndInitialize _window <- createWindow "Hello World" displayCallback $= return () mainLoop }}} {{{ $ runghc GLUT.hs 2017-05-19 12:03:02.199 ghc[24628:669385] GLUT Fatal Error: internal error: NSInternalInconsistencyException, reason: nextEventMatchingMask should only be called from the Main Thread! }}} On the other hand, compiling and running the executable works without issue. Alternatively, you can compile the attached files, which require no dependencies: {{{ $ ghc HsGLUT.c GLUT2.hs [1 of 1] Compiling Main ( GLUT2.hs, GLUT2.o ) Linking GLUT2 ... $ ghci HsGLUT.o GLUT2.hs GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/rscott/.ghci [1 of 1] Compiling Main ( GLUT2.hs, interpreted ) Ok, modules loaded: Main. λ> main 2017-05-19 12:06:15.365 ghc[24671:670166] GLUT Fatal Error: internal error: NSInternalInconsistencyException, reason: nextEventMatchingMask should only be called from the Main Thread! }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Changes (by RyanGlScott): * Attachment "HsGLUT.c" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Changes (by RyanGlScott): * Attachment "GLUT2.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by bgamari): I wonder if this is because `unsafe` FFI calls are performed as `safe` calls in GHCi. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by svenpanne): OpenGL-related stuff heavily depends on thread-local state by design, so it is crucial that there are no hidden thread migrations etc. behind the scenes. Has there been some change in that area? I'm quite sure that this worked in the past, both in compiled form and within GHCi. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Changes (by bgamari): * cc: Jaffacake (added) Comment: I don't believe anything has changed; as far as I know ghc I has always treated unsafe calls as safe. See #8281 where this was recently discussed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by svenpanne): Hmmm, taking a step back, the author of a `foreign import` has to answer the following questions: * Is it OK for the foreign call that (part of) it might run in another OS thread? * Can the foreign call block? * Can the foreign call cause a GC? The last item is probably the same question as: Can the foreign call call back into Haskell? For OpenGL-related calls the answers are: * All OpenGL-related code **must** run in a single thread. There is some arcane Kung Fu in newer OpenGL revisions to allow a bit of multithreading, but it is rarely used and must be done in an explicit manner. * The vast majority of OpenGL calls can't block, and even if they can: Due to the single thread requirement above, it is OK to block everything. * More recent OpenGL versions have the a facility to register debugging callbacks which can fire at any time, so basically all OpenGL calls can cause a GC. All OpenGL calls are done dynamically via native function pointers, something like: {{{#!haskell foreign import ccall "dynamic" dyn376 :: FunPtr (Ptr a -> GLsizei -> Ptr GLsizei -> Ptr GLchar -> IO ()) -> Ptr a -> GLsizei -> Ptr GLsizei -> Ptr GLchar -> IO () }}} `safe` is the default, so this should be correct. The GLUT binding is basically implemented the same way, with the same restrictions imposed by the native API. So the bug IMHO in GHCi is that it somehow silently does some thread switches behind the scenes, although the original program did not talk about multithreading at all. Requiring `runInBoundThread` here doesn't seem right. I think part of the confusion in this ticket and #8281 is that it is highly unclear what `safe` and `unsafe` should actually mean nowadays. In the old days, `safe` just meant "Hey, I can call back into Haskell land, better take care of your data structures for GC etc.". I have no idea what it is supposed to mean in detail today, but it definitely shouldn't be a license for thread migration. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by RyanGlScott): svenpanne, you are correct that this used to work. I just tried this program with GHC 7.10.3 and 8.0.1, and it worked successfully. The only issue was this it gave me this warning: {{{ $ ~/Software/ghc-8.0.1/bin/ghci HsGLUT.o GLUT2.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/rscott/.ghci [1 of 1] Compiling Main ( GLUT2.hs, interpreted ) Ok, modules loaded: Main. λ> main 2017-05-23 08:20:34.277 ghc[59156:853268] WARNING: nextEventMatchingMask should only be called from the Main Thread! This will throw an exception in the future. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by RyanGlScott): There's an extremely similar issue in Racket as well (https://github.com/racket/racket/issues/1491), with the warning appearing in Racket v6.5 and v6.6, and the error popping up in version v6.7. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by svenpanne): Even the warning when using GHCi 7.10.3/8.0.1 looks a bit scary: Some GLUT code doesn't seem to be running in the main OS thread, although the example code doesn't involve any multithreading. GHCi shouldn't do these secret thread migrations: Apart from GLUT and OpenGL there are surely a lot of other libraries/frameworks out there which don't like such a thing... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException
--------------------------------+----------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.0.2
Resolution: | Keywords:
Operating System: MacOS X | Architecture: Unknown/Multiple
Type of failure: GHCi crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
--------------------------------+----------------------------------------
Comment (by Ben Gamari

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.4.1 Comment: I can confirm that comment:8 fixes the example. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13730#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13730: Running GLUT code in GHCi yields NSInternalInconsistencyException
--------------------------------+----------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.4.1
Component: GHCi | Version: 8.0.2
Resolution: fixed | Keywords:
Operating System: MacOS X | Architecture: Unknown/Multiple
Type of failure: GHCi crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
--------------------------------+----------------------------------------
Comment (by Ben Gamari
participants (1)
-
GHC