[GHC] #13210: Can't run terminfo code in GHCi on Windows

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.0.2 System (Linker) | Keywords: | Operating System: Windows Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It's possible this is a duplicate of another runtime linker on Windows issue out there, but I'll post this just in case this really is a unique case. I was attempting to compile the `terminfo` library on Windows, and I actually made it surprisingly far--but I quickly stumbled when I actually tried to run some code in GHCi. First, make sure you have a native Windows version of `ncurses` installed. On MSYS2: {{{ $ pacman -S mingw-w64-x86_64-ncurses }}} And here's a stripped-down version of `terminfo`, which I'll use to demonstrate the bug: {{{#!hs module Main where import Control.Exception import Foreign import Foreign.C.String import Foreign.C.Types data TERMINAL newtype Terminal = Terminal (ForeignPtr TERMINAL) -- Use "unsafe" to make set_curterm faster since it's called quite a bit. foreign import ccall unsafe set_curterm :: Ptr TERMINAL -> IO (Ptr TERMINAL) foreign import ccall "&" del_curterm :: FunPtr (Ptr TERMINAL -> IO ()) foreign import ccall setupterm :: CString -> CInt -> Ptr CInt -> IO () setupTerm :: String -> IO Terminal setupTerm term = withCString term $ \c_term -> with 0 $ \ret_ptr -> do -- NOTE: I believe that for the way we use terminfo -- (i.e. custom output function) -- this parameter does not affect anything. let stdOutput = 1 -- Save the previous terminal to be restored after calling setupterm. old_term <- set_curterm nullPtr -- Call setupterm and check the return value. setupterm c_term stdOutput ret_ptr ret <- peek ret_ptr if (ret /=1) then throwIO $ SetupTermError $ "Couldn't look up terminfo entry " ++ show term else do cterm <- set_curterm old_term fmap Terminal $ newForeignPtr del_curterm cterm data SetupTermError = SetupTermError String instance Show SetupTermError where show (SetupTermError str) = "setupTerm: " ++ str instance Exception SetupTermError where main :: IO () main = do Terminal t <- setupTerm "xterm" print t }}} If you compile this code, it "works" (in the sense that it'll actually call the C code): {{{ $ ghc -lncursesw Terminfo.hs [1 of 1] Compiling Main ( Terminfo.hs, Terminfo.o ) Linking Terminfo.exe ... $ ./Terminfo Terminfo.exe: setupTerm: Couldn't look up terminfo entry "xterm" }}} But attempting to run the same code in GHCi is a disaster: {{{ $ runghc -lncursesw Terminfo.hs ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `nanosleep' ghc.exe: Could not on-demand load symbol '_nc_cookie_init' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_cookie_init' ghc.exe: Could not on-demand load symbol '.refptr._nc_wacs' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `.refptr._nc_wacs' ghc.exe: Could not on-demand load symbol '_nc_WIN_DRIVER' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_WIN_DRIVER' ghc.exe: Could not on-demand load symbol '_nc_get_driver' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_get_driver' ghc.exe: Could not on-demand load symbol '_nc_setupterm_ex' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_setupterm_ex' ghc.exe: Could not on-demand load symbol 'newterm' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `newterm' ghc.exe: Could not on-demand load symbol '.refptr._nc_globals' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `.refptr._nc_globals' ghc.exe: Could not on-demand load symbol '_nc_err_abort' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_err_abort' ghc.exe: Could not on-demand load symbol 'tparm' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `tparm' ghc.exe: Could not on-demand load symbol '.refptr._nc_prescreen' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `.refptr._nc_prescreen' ghc.exe: Could not on-demand load symbol '_nc_outch_sp' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_outch_sp' ghc.exe: Could not on-demand load symbol '.refptr._nc_outch_sp' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `.refptr._nc_outch_sp' ghc.exe: Could not on-demand load symbol '_nc_scrolln_sp' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_scrolln_sp' ghc.exe: Could not on-demand load symbol '.refptr.SP' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `.refptr.SP' ghc.exe: Could not on-demand load symbol '.refptr.cur_term' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `.refptr.cur_term' ghc.exe: Could not on-demand load symbol '_nc_ospeed' ghc.exe: C:/msys64/mingw64/lib/../lib/libncursesw.a: unknown symbol `_nc_ospeed' ghc.exe: Could not on-demand load symbol 'set_curterm' Terminfo.hs: ByteCodeLink: can't find label During interactive linking, GHCi couldn't find the following symbol: set_curterm This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs@haskell.org }}} Also reproducible on GHC HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): No, it's not, will be done for 8.4. It's the same underlying reason. The `mingw` spec file for GCC adds `-lpthread` automatically in certain circumstances. In this case you can get it to work by just adding `-lpthread` manually to your link command. https://github.com/gcc- mirror/gcc/blob/master/gcc/config/i386/mingw32.h#L91 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hm, adding `-lpthread` doesn't seem to work around the issue for me: {{{ $ ../../../Software/ghc/inplace/bin/runghc -lncursesw -lpthread Terminfo.hs GHC runtime linker: fatal error: I found a duplicate definition for symbol ungetch whilst processing object file C:\msys64\mingw64\lib\libncursesw.a The symbol was previously defined in (GHCi built-in symbols) This could be caused by: * Loading two different object files which export the same symbol * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. ghc-stage2.exe: Could not on-demand load symbol 'ungetch_sp' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `ungetch_sp' ghc-stage2.exe: Could not on-demand load symbol 'set_escdelay_sp' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `set_escdelay_sp' ghc-stage2.exe: Could not on-demand load symbol 'newterm' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `newterm' ghc-stage2.exe: Could not on-demand load symbol '.refptr._nc_globals' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `.refptr._nc_globals' ghc-stage2.exe: Could not on-demand load symbol '_nc_err_abort' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `_nc_err_abort' ghc-stage2.exe: Could not on-demand load symbol 'tparm' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `tparm' ghc-stage2.exe: Could not on-demand load symbol '.refptr._nc_prescreen' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `.refptr._nc_prescreen' ghc-stage2.exe: Could not on-demand load symbol '_nc_outch_sp' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `_nc_outch_sp' ghc-stage2.exe: Could not on-demand load symbol '.refptr._nc_outch_sp' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `.refptr._nc_outch_sp' ghc-stage2.exe: Could not on-demand load symbol '_nc_scrolln_sp' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `_nc_scrolln_sp' ghc-stage2.exe: Could not on-demand load symbol '.refptr.SP' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `.refptr.SP' ghc-stage2.exe: Could not on-demand load symbol '.refptr.cur_term' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `.refptr.cur_term' ghc-stage2.exe: Could not on-demand load symbol '_nc_ospeed' ghc-stage2.exe: C:\msys64\mingw64\lib\libncursesw.a: unknown symbol `_nc_ospeed' ghc-stage2.exe: Could not on-demand load symbol 'set_curterm' Terminfo.hs: ByteCodeLink: can't find label During interactive linking, GHCi couldn't find the following symbol: set_curterm This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs@haskell.org }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): That's a different error, now it found a duplicate symbol `ungetch`. Because we're re-exporting it from the RTS and apparently so is `libncursesw.a`. We should probably stop exporting these and add the library that contains them. Or add them as weak symbols. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3154 Wiki Page: | Phab:D3155 -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * differential: => Phab:D3154 Phab:D3155 * milestone: => 8.4.1 Comment: That'll do it. {{{ $ echo main | ../inplace/bin/ghc-stage2.exe ../Terminfo.hs -L/mingw64/lib/ -lncurses --interactive -fforce-recomp GHCi, version 8.1.20170214: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( ..\Terminfo.hs, interpreted ) Ok, modules loaded: Main. *Main> *** Exception: setupTerm: Couldn't look up terminfo entry "xterm" *Main> Leaving GHCi. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3154 Wiki Page: | Phab:D3155 -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: (none) => Phyx- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: Phyx-
Type: bug | Status: patch
Priority: normal | Milestone: 8.4.1
Component: Runtime System | Version: 8.0.2
(Linker) |
Resolution: | Keywords:
Operating System: Windows | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3154
Wiki Page: | Phab:D3155
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: fixed | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3154 Wiki Page: | Phab:D3155 -------------------------------------+------------------------------------- Changes (by Phyx-): * status: patch => closed * resolution: => fixed * milestone: 8.4.1 => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3154 Wiki Page: | Phab:D3155 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: Phyx- => (none) * status: closed => new * resolution: fixed => Comment: Alas, it seems like this code is once again broken. On GHC 8.2.1 and 8.2.2-rc3, running: {{{ $ runghc -lncursesw Terminfo.hs }}} In MSYS2 simply exits early with exit code 127, and in PowerShell, it crashes with the following pop-up window: {{{ [Window Title] ghc.exe [Main Instruction] ghc.exe has stopped working [Content] A problem caused the program to stop working correctly. Windows will close the program and notify you if a solution is available. [Close program] }}} Using Phyx-'s modified GHC 8.3 build, running that same command produces a stack trace: {{{ $ ..\..\..\Software\ghc-8.3.20171021\bin\runghc -lncursesw .\Terminfo.hs Access violation in generated code when reading 0xffffffffffffffff Attempting to reconstruct a stack trace... Frame Code address * 0x87af500 0x7ffa30adefc4 C:\WINDOWS\System32\msvcrt.dll+0x2efc4 * 0x87af540 0x7ffa30adf074 C:\WINDOWS\System32\msvcrt.dll+0x2f074 * 0x87af548 0xa275038 C:\msys64\mingw64\lib\libncursesw.a(db_iterator.o)+0x68 (_nc_tic_dir+0x118) * 0x87af550 0x10 * 0x87af558 0x398 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13210: Can't run terminfo code in GHCi on Windows -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3154 Wiki Page: | Phab:D3155 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: 8.2.1 => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13210#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC