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

GHC ghc-devs at haskell.org
Fri May 19 19:07:21 UTC 2017


#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


More information about the ghc-tickets mailing list