[commit: packages/unix] master: Fix SIGINFO and SIGWINCH. (3c4ced4)

git at git.haskell.org git at git.haskell.org
Thu Mar 19 15:51:04 UTC 2015


Repository : ssh://git@git.haskell.org/unix

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3c4ced48d5d82bc3042fdd058e684e87e7036166/unix

>---------------------------------------------------------------

commit 3c4ced48d5d82bc3042fdd058e684e87e7036166
Author: Erik de Castro Lopo <erikd at mega-nerd.com>
Date:   Fri Dec 19 14:47:43 2014 +1100

    Fix SIGINFO and SIGWINCH.
    
    It seems these two signals have not been working since at least
    2009. Detection of these signals seems to have never been added to
    the configure.ac script and the code guarded by #ifdef then bit-rotted
    (the idiom used to handle these signals seems to have been abandoned
    for something simpler/better in 2009). This fix simply handles these
    signals the same way the other signals are handled in
    System/Posix/Signals.hsc.
    
    Closes #30 and #31


>---------------------------------------------------------------

3c4ced48d5d82bc3042fdd058e684e87e7036166
 System/Posix/Signals/Exts.hsc | 49 +++++++++++++++----------------------------
 cbits/HsUnix.c                |  7 -------
 changelog.md                  |  2 ++
 configure.ac                  |  2 +-
 include/HsUnix.h              |  7 -------
 5 files changed, 20 insertions(+), 47 deletions(-)

diff --git a/System/Posix/Signals/Exts.hsc b/System/Posix/Signals/Exts.hsc
index a889340..95796a2 100644
--- a/System/Posix/Signals/Exts.hsc
+++ b/System/Posix/Signals/Exts.hsc
@@ -1,10 +1,7 @@
+{-# LANGUAGE CPP #-}
 #ifdef __GLASGOW_HASKELL__
-#if defined(SIGINFO) || defined(SIGWINCH)
-{-# LANGUAGE Trustworthy #-}
-#else
 {-# LANGUAGE Safe #-}
 #endif
-#endif
 
 -----------------------------------------------------------------------------
 -- |
@@ -20,45 +17,33 @@
 --
 -----------------------------------------------------------------------------
 
-#include "HsUnix.h"
-
-module System.Posix.Signals.Exts (
-  module System.Posix.Signals
+#include "HsUnixConfig.h"
+##include "HsUnixConfig.h"
 
-#ifdef SIGINFO
-  , infoEvent, sigINFO
-#endif
-#ifdef SIGWINCH
-  , windowChange, sigWINCH
+#ifdef HAVE_SIGNAL_H
+#include <signal.h>
 #endif
 
+module System.Posix.Signals.Exts (
+  module System.Posix.Signals
+  , sigINFO
+  , sigWINCH
+  , infoEvent
+  , windowChange
   ) where
 
 import Foreign.C
 import System.Posix.Signals
 
-#ifdef __HUGS__
-# ifdef SIGINFO
-sigINFO   = (#const SIGINFO)   :: CInt
-# endif
-# ifdef SIGWINCH
-sigWINCH  = (#const SIGWINCH)  :: CInt
-# endif
-#else /* !HUGS */
-# ifdef SIGINFO
-foreign import ccall unsafe "__hsunix_SIGINFO"   sigINFO   :: CInt
-# endif
-# ifdef SIGWINCH
-foreign import ccall unsafe "__hsunix_SIGWINCH"   sigWINCH   :: CInt
-# endif
-#endif /* !HUGS */
+sigINFO   :: CInt
+sigINFO   = CONST_SIGINFO
+
+sigWINCH   :: CInt
+sigWINCH   = CONST_SIGWINCH
+
 
-#ifdef SIGINFO
 infoEvent :: Signal
 infoEvent = sigINFO
-#endif
 
-#ifdef SIGWINCH
 windowChange :: Signal
 windowChange = sigWINCH
-#endif
diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c
index db97de2..60f19bc 100644
--- a/cbits/HsUnix.c
+++ b/cbits/HsUnix.c
@@ -24,13 +24,6 @@ void *__hsunix_rtldNext (void) {return RTLD_NEXT;}
 void *__hsunix_rtldDefault (void) {return RTLD_DEFAULT;}
 #endif
 
-#ifdef SIGINFO
-int __hsunix_SIGINFO(void)	{ return SIGINFO; }
-#endif
-#ifdef SIGWINCH
-int __hsunix_SIGWINCH(void)	{ return SIGWINCH; }
-#endif
-
 // lstat is a macro on some platforms, so we need a wrapper:
 int __hsunix_lstat(const char *path, struct stat *buf) 
 { 
diff --git a/changelog.md b/changelog.md
index db6bb48..5d682bc 100644
--- a/changelog.md
+++ b/changelog.md
@@ -25,6 +25,8 @@
      - `fileAdvise` (aka `posix_fadvise(2)`), and
      - `fileAllocate` (aka `posix_fallocate(2)`)
 
+  * Fix SIGINFO and SIGWINCH definitions
+
 ## 2.7.0.1  *Mar 2014*
 
   * Bundled with GHC 7.8.1
diff --git a/configure.ac b/configure.ac
index 1c82c36..f7b1afb 100644
--- a/configure.ac
+++ b/configure.ac
@@ -76,7 +76,7 @@ AC_CHECK_FUNCS([posix_fadvise posix_fallocate])
 AC_SEARCH_LIBS(shm_open, rt, [AC_CHECK_FUNCS([shm_open shm_unlink])])
 AS_IF([test "x$ac_cv_search_shm_open" = x-lrt], [EXTRA_LIBS="$EXTRA_LIBS rt"])
 
-FP_CHECK_CONSTS([SIGABRT SIGALRM SIGBUS SIGCHLD SIGCONT SIGFPE SIGHUP SIGILL SIGINT SIGKILL SIGPIPE SIGQUIT SIGSEGV SIGSTOP SIGTERM SIGTSTP SIGTTIN SIGTTOU SIGUSR1 SIGUSR2 SIGPOLL SIGPROF SIGSYS SIGTRAP SIGURG SIGVTALRM SIGXCPU SIGXFSZ SIG_BLOCK SIG_SETMASK SIG_UNBLOCK], [
+FP_CHECK_CONSTS([SIGABRT SIGALRM SIGBUS SIGCHLD SIGCONT SIGFPE SIGHUP SIGILL SIGINT SIGKILL SIGPIPE SIGQUIT SIGSEGV SIGSTOP SIGTERM SIGTSTP SIGTTIN SIGTTOU SIGUSR1 SIGUSR2 SIGPOLL SIGPROF SIGSYS SIGTRAP SIGURG SIGVTALRM SIGXCPU SIGXFSZ SIG_BLOCK SIG_SETMASK SIG_UNBLOCK SIGINFO SIGWINCH], [
 #if HAVE_SIGNAL_H
 #include <signal.h>
 #endif])
diff --git a/include/HsUnix.h b/include/HsUnix.h
index a23f0f9..ba3e053 100644
--- a/include/HsUnix.h
+++ b/include/HsUnix.h
@@ -119,13 +119,6 @@ fall back to O_FSYNC, which should be the same */
 #define O_SYNC O_FSYNC
 #endif
 
-#ifdef SIGINFO
-int __hsunix_SIGINFO();
-#endif
-#ifdef SIGWINCH
-int __hsunix_SIGWINCH();
-#endif
-
 // lstat is a macro on some platforms, so we need a wrapper:
 int __hsunix_lstat(const char *path, struct stat *buf);
 



More information about the ghc-commits mailing list