Skip to content
Snippets Groups Projects
Commit 3c4ced48 authored by Erik de Castro Lopo's avatar Erik de Castro Lopo Committed by Herbert Valerio Riedel
Browse files

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
parent 757bf44b
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
#ifdef __GLASGOW_HASKELL__
#if defined(SIGINFO) || defined(SIGWINCH)
{-# LANGUAGE Trustworthy #-}
#else
{-# LANGUAGE Safe #-}
#endif
#endif
-----------------------------------------------------------------------------
-- |
-- Module : System.Posix.Signals.Exts
-- Copyright : (c) The University of Glasgow 2002
-- License : BSD-style (see the file libraries/base/LICENSE)
--
--
-- Maintainer : libraries@haskell.org
-- Stability : provisional
-- Portability : non-portable (requires POSIX, includes Linuxisms/BSDisms)
......@@ -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
......@@ -21,14 +21,7 @@ void *__hsunix_rtldNext (void) {return RTLD_NEXT;}
#endif
#ifdef HAVE_RTLDDEFAULT
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; }
void *__hsunix_rtldDefault (void) {return RTLD_DEFAULT;}
#endif
// lstat is a macro on some platforms, so we need a wrapper:
......
......@@ -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
......
......@@ -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])
......
......@@ -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);
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment