diff --git a/System/Posix/Signals/Exts.hsc b/System/Posix/Signals/Exts.hsc
index a8893404d690a4dbd6a4375161c8c35eb3718b75..95796a23dacd5f7a03be53b38683bf5c555ee96d 100644
--- a/System/Posix/Signals/Exts.hsc
+++ b/System/Posix/Signals/Exts.hsc
@@ -1,17 +1,14 @@
+{-# 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
diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c
index db97de2a01a5e18b83c0370ff87b05ff8413c314..60f19bcac3ea3612b4b1241f1106c3b6751d39e3 100644
--- a/cbits/HsUnix.c
+++ b/cbits/HsUnix.c
@@ -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:
diff --git a/changelog.md b/changelog.md
index db6bb48d48defbeccabadf237fc595898c28ca46..5d682bcc4e9a9eb727f2dd684739cad9238a79fe 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 1c82c368db045e385d0b8470be2cba3c4d2c2ff3..f7b1afbc874673420e244a68ad74a1dab47b7fab 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 a23f0f90cc8281f559728c6d34ff1918254796b8..ba3e053e818b55ca16d432ca725ea9c2851274f1 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);