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

GHC ghc-devs at haskell.org
Mon Jan 30 15:20:35 UTC 2017


#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 at 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


More information about the ghc-tickets mailing list