Subject: Remove use of cur_term global struct From: Scott Bahling sbahling@suse.com Date: 2015-10-04 With the move to ncurses6, it has been decided by the openSUSE developer to build the library in threaded mode only. In threaded mode, the global variables are protected and not exported. ghc-terminfo was accessing (reading and writing) the cur_term global so it doesn't work with the openSUSE threaded ncurses6 library. This is an attempt to remove the need to access cur_term and rely only on the low-level functions. First, cur_term was being set to a null pointer in order to force ncurses setupterm() to return new struct instead of a copy of the current when the terminal name is the same. Actually (and unfortunately) setupterm() does not return the struct but rather set the global cur_term. Reading the ncurses code, and the NEWS file, it appears that the behavior of setupterm() had been changed quite some time ago, and no longer returns a copy of the struct (internal 'reuse' option) (NEWS 20041127). The code seems to confirm this, so setting cur_term to a null pointer shouldn't really be required - we remove poke cur_term! That's great, but the we still have the problem that setupterm() doesn't return the terminal struct that is required later to setup the cleanup routine of the Terminal type (del_curterm cterm). The only function that appears to return the cur_term pointer is set_curterm() which has the side effect of overwriting the current pointer in the process :/ So, we call set_curterm() with a null pointer, retrieving the former, cur_term pointer for our use in the cterm instance, and then call set_curterm() again with the former pointer to set it back again.... whew! Having looked at the ncurses set_curterm() code it seems it handles a null pointer in the way we would need. Later in the withCurTerm function we use virtually the same trick to relieve the need to peek into the cur_term global. I'm not so sure if this is Haskell correct code though. Someone with more Haskell programming knowledge than me should review this patch. It still needs to be tested as well. --- diff -Nrup a/libraries/terminfo/System/Console/Terminfo/Base.hs b/libraries/terminfo/System/Console/Terminfo/Base.hs --- a/libraries/terminfo/System/Console/Terminfo/Base.hs 2015-02-25 06:13:15.000000000 +0100 +++ b/libraries/terminfo/System/Console/Terminfo/Base.hs 2015-10-03 21:40:09.106028237 +0200 @@ -63,7 +63,6 @@ import Data.Typeable data TERMINAL newtype Terminal = Terminal (ForeignPtr TERMINAL) -foreign import ccall "&" cur_term :: Ptr (Ptr TERMINAL) foreign import ccall set_curterm :: Ptr TERMINAL -> IO (Ptr TERMINAL) foreign import ccall "&" del_curterm :: FunPtr (Ptr TERMINAL -> IO ()) @@ -73,19 +72,12 @@ foreign import ccall setupterm :: CStrin -- -- Throws a 'SetupTermError' if the terminfo database could not be read. setupTerm :: String -> IO Terminal -setupTerm term = bracket (peek cur_term) (poke cur_term) $ \_ -> - withCString term $ \c_term -> +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 - {-- Force ncurses to return a new struct rather than - a copy of the current one (which it would do if the - terminal names are the same). This prevents problems - when calling del_term on a struct shared by more than one - Terminal. --} - poke cur_term nullPtr -- Call setupterm and check the return value. setupterm c_term stdOutput ret_ptr ret <- peek ret_ptr @@ -93,7 +85,12 @@ setupTerm term = bracket (peek cur_term) then throwIO $ SetupTermError $ "Couldn't look up terminfo entry " ++ show term else do - cterm <- peek cur_term + -- There is no function to simply return the cur_term pointer. + -- We call set_curterm with nullPtr which will give us + -- the value of the old cur_term and then we set it back + -- again. + cterm <- set_curterm nullPtr + set_curterm cterm fmap Terminal $ newForeignPtr del_curterm cterm data SetupTermError = SetupTermError String @@ -120,15 +117,10 @@ setupTermFromEnv = do -- TODO: this isn't really thread-safe... withCurTerm :: Terminal -> IO a -> IO a withCurTerm (Terminal term) f = withForeignPtr term $ \cterm -> do - old_term <- peek cur_term - if old_term /= cterm - then do - _ <- set_curterm cterm - x <- f - _ <- set_curterm old_term - return x - else f - + old_term <- set_curterm cterm + x <- f + set_curterm old_term + return x ----------------------