diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index 65445e410c2bfacad84112830ab78e8120ecb921..db6666cce61b6ad5fd82ed25a2c2adec623ca55e 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -1345,7 +1345,7 @@ type HasCallStack = (() :: Constraint)
 #endif
 
 -- | A call stack constraint, but only when 'isDebugOn'.
-#if DEBUG
+#ifdef DEBUG
 type HasDebugCallStack = HasCallStack
 #else
 type HasDebugCallStack = (() :: Constraint)
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index deee24ab33fd4bc71587705d335a5ba3781a5cdc..f3154c6fc5af09ac08949c6294b3094b5a5d4425 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -379,7 +379,7 @@ findEditor :: IO String
 findEditor = do
   getEnv "EDITOR"
     `catchIO` \_ -> do
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
         win <- System.Win32.getWindowsDirectory
         return (win </> "notepad.exe")
 #else
diff --git a/includes/CodeGen.Platform.hs b/includes/CodeGen.Platform.hs
index 46550af213b8f6eac2d0c9ec48e608f7df074002..6691484f663e0fb398d1a5ae9bbe007a800bc618 100644
--- a/includes/CodeGen.Platform.hs
+++ b/includes/CodeGen.Platform.hs
@@ -1,6 +1,7 @@
 
 import CmmExpr
-#if !(MACHREGS_i386 || MACHREGS_x86_64 || MACHREGS_sparc || MACHREGS_powerpc)
+#if !(defined(MACHREGS_i386) || defined(MACHREGS_x86_64) \
+    || defined(MACHREGS_sparc) || defined(MACHREGS_powerpc))
 import Panic
 #endif
 import Reg
@@ -8,9 +9,9 @@ import Reg
 #include "ghcautoconf.h"
 #include "stg/MachRegs.h"
 
-#if MACHREGS_i386 || MACHREGS_x86_64
+#if defined(MACHREGS_i386) || defined(MACHREGS_x86_64)
 
-# if MACHREGS_i386
+# if defined(MACHREGS_i386)
 #  define eax 0
 #  define ebx 1
 #  define ecx 2
@@ -21,7 +22,7 @@ import Reg
 #  define esp 7
 # endif
 
-# if MACHREGS_x86_64
+# if defined(MACHREGS_x86_64)
 #  define rax   0
 #  define rbx   1
 #  define rcx   2
@@ -103,7 +104,8 @@ import Reg
 -- I'm not sure if these are the correct numberings.
 -- Normally, the register names are just stringified as part of the REG() macro
 
-#elif MACHREGS_powerpc || MACHREGS_arm || MACHREGS_aarch64
+#elif defined(MACHREGS_powerpc) || defined(MACHREGS_arm) \
+    || defined(MACHREGS_aarch64)
 
 # define r0 0
 # define r1 1
@@ -138,9 +140,10 @@ import Reg
 # define r30 30
 # define r31 31
 
--- See note above. These aren't actually used for anything except satisfying the compiler for globalRegMaybe
--- so I'm unsure if they're the correct numberings, should they ever be attempted to be used in the NCG. 
-#if MACHREGS_aarch64 || MACHREGS_arm
+-- See note above. These aren't actually used for anything except satisfying
+-- the compiler for globalRegMaybe so I'm unsure if they're the correct
+-- numberings, should they ever be attempted to be used in the NCG.
+#if defined(MACHREGS_aarch64) || defined(MACHREGS_arm)
 # define s0 32
 # define s1 33
 # define s2 34
@@ -208,7 +211,7 @@ import Reg
 # define d31 63
 #endif
 
-# if MACHREGS_darwin
+# if defined(MACHREGS_darwin)
 #  define f0  32
 #  define f1  33
 #  define f2  34
@@ -276,7 +279,7 @@ import Reg
 #  define fr31 63
 # endif
 
-#elif MACHREGS_sparc
+#elif defined(MACHREGS_sparc)
 
 # define g0  0
 # define g1  1
@@ -631,7 +634,9 @@ haveRegBase = False
 -- in a real machine register, otherwise returns @'Just' reg@, where
 -- reg is the machine register it is stored in.
 globalRegMaybe :: GlobalReg -> Maybe RealReg
-#if MACHREGS_i386 || MACHREGS_x86_64 || MACHREGS_sparc || MACHREGS_powerpc || MACHREGS_arm || MACHREGS_aarch64
+#if defined(MACHREGS_i386) || defined(MACHREGS_x86_64) \
+    || defined(MACHREGS_sparc) || defined(MACHREGS_powerpc) \
+    || defined(MACHREGS_arm) || defined(MACHREGS_aarch64)
 # ifdef REG_Base
 globalRegMaybe BaseReg                  = Just (RealRegSingle REG_Base)
 # endif
@@ -685,7 +690,7 @@ globalRegMaybe (FloatReg 6)             = Just (RealRegSingle REG_F6)
 # endif
 # ifdef REG_D1
 globalRegMaybe (DoubleReg 1)            =
-#  if MACHREGS_sparc
+#  if defined(MACHREGS_sparc)
                                           Just (RealRegPair REG_D1 (REG_D1 + 1))
 #  else
                                           Just (RealRegSingle REG_D1)
@@ -693,7 +698,7 @@ globalRegMaybe (DoubleReg 1)            =
 # endif
 # ifdef REG_D2
 globalRegMaybe (DoubleReg 2)            =
-#  if MACHREGS_sparc
+#  if defined(MACHREGS_sparc)
                                           Just (RealRegPair REG_D2 (REG_D2 + 1))
 #  else
                                           Just (RealRegSingle REG_D2)
@@ -701,7 +706,7 @@ globalRegMaybe (DoubleReg 2)            =
 # endif
 # ifdef REG_D3
 globalRegMaybe (DoubleReg 3)            =
-#  if MACHREGS_sparc
+#  if defined(MACHREGS_sparc)
                                           Just (RealRegPair REG_D3 (REG_D3 + 1))
 #  else
                                           Just (RealRegSingle REG_D3)
@@ -709,7 +714,7 @@ globalRegMaybe (DoubleReg 3)            =
 # endif
 # ifdef REG_D4
 globalRegMaybe (DoubleReg 4)            =
-#  if MACHREGS_sparc
+#  if defined(MACHREGS_sparc)
                                           Just (RealRegPair REG_D4 (REG_D4 + 1))
 #  else
                                           Just (RealRegSingle REG_D4)
@@ -717,7 +722,7 @@ globalRegMaybe (DoubleReg 4)            =
 # endif
 # ifdef REG_D5
 globalRegMaybe (DoubleReg 5)            =
-#  if MACHREGS_sparc
+#  if defined(MACHREGS_sparc)
                                           Just (RealRegPair REG_D5 (REG_D5 + 1))
 #  else
                                           Just (RealRegSingle REG_D5)
@@ -725,7 +730,7 @@ globalRegMaybe (DoubleReg 5)            =
 # endif
 # ifdef REG_D6
 globalRegMaybe (DoubleReg 6)            =
-#  if MACHREGS_sparc
+#  if defined(MACHREGS_sparc)
                                           Just (RealRegPair REG_D6 (REG_D6 + 1))
 #  else
                                           Just (RealRegSingle REG_D6)
@@ -751,7 +756,7 @@ globalRegMaybe (XmmReg 5)               = Just (RealRegSingle REG_XMM5)
 globalRegMaybe (XmmReg 6)               = Just (RealRegSingle REG_XMM6)
 #  endif
 # endif
-# if MAX_REAL_YMM_REG != 0
+# if defined MAX_REAL_YMM_REG && MAX_REAL_YMM_REG != 0
 #  ifdef REG_YMM1
 globalRegMaybe (YmmReg 1)               = Just (RealRegSingle REG_YMM1)
 #  endif
@@ -771,7 +776,7 @@ globalRegMaybe (YmmReg 5)               = Just (RealRegSingle REG_YMM5)
 globalRegMaybe (YmmReg 6)               = Just (RealRegSingle REG_YMM6)
 #  endif
 # endif
-# if MAX_REAL_ZMM_REG != 0
+# if defined MAX_REAL_ZMM_REG && MAX_REAL_ZMM_REG != 0
 #  ifdef REG_ZMM1
 globalRegMaybe (ZmmReg 1)               = Just (RealRegSingle REG_ZMM1)
 #  endif
@@ -819,7 +824,7 @@ globalRegMaybe CurrentNursery           = Just (RealRegSingle REG_CurrentNursery
 globalRegMaybe MachSp                   = Just (RealRegSingle REG_MachSp)
 # endif
 globalRegMaybe _                        = Nothing
-#elif MACHREGS_NO_REGS
+#elif defined MACHREGS_NO_REGS
 globalRegMaybe _ = Nothing
 #else
 globalRegMaybe = panic "globalRegMaybe not defined for this platform"
@@ -827,14 +832,14 @@ globalRegMaybe = panic "globalRegMaybe not defined for this platform"
 
 freeReg :: RegNo -> Bool
 
-#if MACHREGS_i386 || MACHREGS_x86_64
+#if defined(MACHREGS_i386) || defined(MACHREGS_x86_64)
 
-# if MACHREGS_i386
+# if defined(MACHREGS_i386)
 freeReg esp = False -- %esp is the C stack pointer
 freeReg esi = False -- Note [esi/edi not allocatable]
 freeReg edi = False
 # endif
-# if MACHREGS_x86_64
+# if defined(MACHREGS_x86_64)
 freeReg rsp = False  --        %rsp is the C stack pointer
 # endif
 
@@ -875,14 +880,14 @@ freeRegBase REG_HpLim = False
 -- their liveness accurately.
 freeRegBase _ = True
 
-#elif MACHREGS_powerpc
+#elif defined(MACHREGS_powerpc)
 
 freeReg 0 = False -- Used by code setting the back chain pointer
                   -- in stack reallocations on Linux
                   -- r0 is not usable in all insns so also reserved
                   -- on Darwin.
 freeReg 1 = False -- The Stack Pointer
-# if !MACHREGS_darwin
+# if !defined(MACHREGS_darwin)
 -- most non-darwin powerpc OSes use r2 as a TOC pointer or something like that
 freeReg 2 = False
 freeReg 13 = False -- reserved for system thread ID on 64 bit
@@ -983,7 +988,7 @@ freeReg REG_HpLim = False
 # endif
 freeReg _ = True
 
-#elif MACHREGS_sparc
+#elif defined(MACHREGS_sparc)
 
 -- SPARC regs used by the OS / ABI
 -- %g0(r0) is always zero
diff --git a/includes/Stg.h b/includes/Stg.h
index 939bed644498b4496bb8c0bb57dc39a8e95b6cfa..88c8794726cfde9149ecb1423e82451dfef65263 100644
--- a/includes/Stg.h
+++ b/includes/Stg.h
@@ -147,7 +147,7 @@
 // to force gnu90-style 'external inline' semantics.
 #if defined(FORCE_GNU_INLINE)
 // disable auto-detection since HAVE_GNU_INLINE has been defined externally
-#elif __GNUC_GNU_INLINE__ && __GNUC__ == 4 && __GNUC_MINOR__ == 2
+#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2
 // GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first
 // release to properly support C99 inline semantics), and therefore warned when
 // using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))`
@@ -155,14 +155,14 @@
 # define FORCE_GNU_INLINE 1
 #endif
 
-#if FORCE_GNU_INLINE
+#ifdef FORCE_GNU_INLINE
 // Force compiler into gnu90 semantics
 # if defined(KEEP_INLINES)
 #  define EXTERN_INLINE inline __attribute__((gnu_inline))
 # else
 #  define EXTERN_INLINE extern inline __attribute__((gnu_inline))
 # endif
-#elif __GNUC_GNU_INLINE__
+#elif defined(__GNUC_GNU_INLINE__)
 // we're currently in gnu90 inline mode by default and
 // __attribute__((gnu_inline)) may not be supported, so better leave it off
 # if defined(KEEP_INLINES)
diff --git a/includes/rts/OSThreads.h b/includes/rts/OSThreads.h
index 2ebbd1e0f19f5e141aa99c6db0c3f7ba839683cf..fd9b44cc55ea3d46f4f13e7b6c3946fcd27d7af8 100644
--- a/includes/rts/OSThreads.h
+++ b/includes/rts/OSThreads.h
@@ -17,7 +17,7 @@
 
 #if defined(HAVE_PTHREAD_H) && !defined(mingw32_HOST_OS)
 
-#if CMINUSMINUS
+#ifdef CMINUSMINUS
 
 #define OS_ACQUIRE_LOCK(mutex) foreign "C" pthread_mutex_lock(mutex)
 #define OS_RELEASE_LOCK(mutex) foreign "C" pthread_mutex_unlock(mutex)
@@ -76,7 +76,7 @@ EXTERN_INLINE int TRY_ACQUIRE_LOCK(pthread_mutex_t *mutex)
 
 # elif defined(HAVE_WINDOWS_H)
 
-#if CMINUSMINUS
+#ifdef CMINUSMINUS
 
 /* We jump through a hoop here to get a CCall EnterCriticalSection
    and LeaveCriticalSection, as that's what C-- wants. */
diff --git a/includes/stg/HaskellMachRegs.h b/includes/stg/HaskellMachRegs.h
index e95cefd82207bb8ae0c1e473002ac293072b33a0..00199d78584aa12a22eec12c59d2050e1f141b57 100644
--- a/includes/stg/HaskellMachRegs.h
+++ b/includes/stg/HaskellMachRegs.h
@@ -33,14 +33,34 @@
 
 #define MACHREGS_NO_REGS 0
 
-#define MACHREGS_i386     i386_TARGET_ARCH
-#define MACHREGS_x86_64   x86_64_TARGET_ARCH
-#define MACHREGS_powerpc  (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH \
-                || powerpc64le_TARGET_ARCH || rs6000_TARGET_ARCH)
-#define MACHREGS_sparc    sparc_TARGET_ARCH
-#define MACHREGS_arm      arm_TARGET_ARCH
-#define MACHREGS_aarch64  aarch64_TARGET_ARCH
-#define MACHREGS_darwin   darwin_TARGET_OS
+#ifdef i386_TARGET_ARCH
+#define MACHREGS_i386     1
+#endif
+
+#ifdef x86_64_TARGET_ARCH
+#define MACHREGS_x86_64   1
+#endif
+
+#if defined(powerpc_TARGET_ARCH) || defined(powerpc64_TARGET_ARCH) \
+            || defined(powerpc64le_TARGET_ARCH) || defined(rs6000_TARGET_ARCH)
+#define MACHREGS_powerpc  1
+#endif
+
+#ifdef sparc_TARGET_ARCH
+#define MACHREGS_sparc    1
+#endif
+
+#ifdef arm_TARGET_ARCH
+#define MACHREGS_arm      1
+#endif
+
+#ifdef aarch64_TARGET_ARCH
+#define MACHREGS_aarch64  1
+#endif
+
+#ifdef darwin_TARGET_OS
+#define MACHREGS_darwin   1
+#endif
 
 #endif
 
diff --git a/includes/stg/MachRegs.h b/includes/stg/MachRegs.h
index 232ce0381019ae700824f453a904d54844554559..bed6b903248b8fab8c34a204c109130628fd31d6 100644
--- a/includes/stg/MachRegs.h
+++ b/includes/stg/MachRegs.h
@@ -82,7 +82,7 @@
    Leaving SpLim out of the picture.
    -------------------------------------------------------------------------- */
 
-#if MACHREGS_i386
+#ifdef MACHREGS_i386
 
 #define REG(x) __asm__("%" #x)
 
@@ -156,7 +156,7 @@
 
   --------------------------------------------------------------------------- */
 
-#elif MACHREGS_x86_64
+#elif defined(MACHREGS_x86_64)
 
 #define REG(x) __asm__("%" #x)
 
@@ -303,7 +303,7 @@ the stack. See Note [Overlapping global registers] for implications.
    We can do the Whole Business with callee-save registers only!
    -------------------------------------------------------------------------- */
 
-#elif MACHREGS_powerpc
+#elif defined(MACHREGS_powerpc)
 
 #define REG(x) __asm__(#x)
 
@@ -316,7 +316,7 @@ the stack. See Note [Overlapping global registers] for implications.
 #define REG_R7          r20
 #define REG_R8          r21
 
-#if MACHREGS_darwin
+#ifdef MACHREGS_darwin
 
 #define REG_F1          f14
 #define REG_F2          f15
@@ -442,7 +442,7 @@ the stack. See Note [Overlapping global registers] for implications.
 
    -------------------------------------------------------------------------- */
 
-#elif MACHREGS_sparc
+#elif defined(MACHREGS_sparc)
 
 #define REG(x) __asm__("%" #x)
 
@@ -521,7 +521,7 @@ the stack. See Note [Overlapping global registers] for implications.
    d16-d31/q8-q15        Argument / result/ scratch registers
    ----------------------------------------------------------------------------- */
 
-#elif MACHREGS_arm
+#elif defined(MACHREGS_arm)
 
 #define REG(x) __asm__(#x)
 
@@ -578,7 +578,7 @@ the stack. See Note [Overlapping global registers] for implications.
 
    ----------------------------------------------------------------------------- */
 
-#elif MACHREGS_aarch64
+#elif defined(MACHREGS_aarch64)
 
 #define REG(x) __asm__(#x)
 
diff --git a/includes/stg/RtsMachRegs.h b/includes/stg/RtsMachRegs.h
index 29262dc17ab42d516a06096272917a0d1147ade8..e6298cf8c9d3158fdf3c860e7e699ad5f474e73d 100644
--- a/includes/stg/RtsMachRegs.h
+++ b/includes/stg/RtsMachRegs.h
@@ -39,14 +39,34 @@
 
 #define MACHREGS_NO_REGS 0
 
-#define MACHREGS_i386     i386_HOST_ARCH
-#define MACHREGS_x86_64   x86_64_HOST_ARCH
-#define MACHREGS_powerpc  (powerpc_HOST_ARCH || powerpc64_HOST_ARCH \
-        || powerpc64le_HOST_ARCH || rs6000_HOST_ARCH)
-#define MACHREGS_sparc    sparc_HOST_ARCH
-#define MACHREGS_arm      arm_HOST_ARCH
-#define MACHREGS_aarch64  aarch64_HOST_ARCH
-#define MACHREGS_darwin   darwin_HOST_OS
+#ifdef i386_HOST_ARCH
+#define MACHREGS_i386     1
+#endif
+
+#ifdef x86_64_HOST_ARCH
+#define MACHREGS_x86_64   1
+#endif
+
+#if defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
+        || defined(powerpc64le_HOST_ARCH) || defined(rs6000_HOST_ARCH)
+#define MACHREGS_powerpc  1
+#endif
+
+#ifdef sparc_HOST_ARCH
+#define MACHREGS_sparc    1
+#endif
+
+#ifdef arm_HOST_ARCH
+#define MACHREGS_arm      1
+#endif
+
+#ifdef aarch64_HOST_ARCH
+#define MACHREGS_aarch64  1
+#endif
+
+#ifdef darwin_HOST_OS
+#define MACHREGS_darwin   1
+#endif
 
 #endif
 
diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h
index 0e806b671617c0da6efdef528333f31ef8e84916..21ab0e1214d7cdc3c29b4f4ba2d6a44bcdc96f0c 100644
--- a/includes/stg/SMP.h
+++ b/includes/stg/SMP.h
@@ -14,7 +14,7 @@
 #ifndef SMP_H
 #define SMP_H
 
-#if arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6)
+#if defined(arm_HOST_ARCH) && defined(arm_HOST_ARCH_PRE_ARMv6)
 void arm_atomic_spin_lock(void);
 void arm_atomic_spin_unlock(void);
 #endif
@@ -187,14 +187,15 @@ EXTERN_INLINE void
 write_barrier(void) {
 #if defined(NOSMP)
     return;
-#elif i386_HOST_ARCH || x86_64_HOST_ARCH
+#elif defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH)
     __asm__ __volatile__ ("" : : : "memory");
-#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+#elif defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
+    || defined(powerpc64le_HOST_ARCH)
     __asm__ __volatile__ ("lwsync" : : : "memory");
-#elif sparc_HOST_ARCH
+#elif defined(sparc_HOST_ARCH)
     /* Sparc in TSO mode does not require store/store barriers. */
     __asm__ __volatile__ ("" : : : "memory");
-#elif (arm_HOST_ARCH) || aarch64_HOST_ARCH
+#elif defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)
     __asm__ __volatile__ ("dmb  st" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
@@ -205,17 +206,18 @@ EXTERN_INLINE void
 store_load_barrier(void) {
 #if defined(NOSMP)
     return;
-#elif i386_HOST_ARCH
+#elif defined(i386_HOST_ARCH)
     __asm__ __volatile__ ("lock; addl $0,0(%%esp)" : : : "memory");
-#elif x86_64_HOST_ARCH
+#elif defined(x86_64_HOST_ARCH)
     __asm__ __volatile__ ("lock; addq $0,0(%%rsp)" : : : "memory");
-#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+#elif defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
+    || defined(powerpc64le_HOST_ARCH)
     __asm__ __volatile__ ("sync" : : : "memory");
-#elif sparc_HOST_ARCH
+#elif defined(sparc_HOST_ARCH)
     __asm__ __volatile__ ("membar #StoreLoad" : : : "memory");
-#elif arm_HOST_ARCH
+#elif defined(arm_HOST_ARCH)
     __asm__ __volatile__ ("dmb" : : : "memory");
-#elif aarch64_HOST_ARCH
+#elif defined(aarch64_HOST_ARCH)
     __asm__ __volatile__ ("dmb sy" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
@@ -226,18 +228,19 @@ EXTERN_INLINE void
 load_load_barrier(void) {
 #if defined(NOSMP)
     return;
-#elif i386_HOST_ARCH
+#elif defined(i386_HOST_ARCH)
     __asm__ __volatile__ ("" : : : "memory");
-#elif x86_64_HOST_ARCH
+#elif defined(x86_64_HOST_ARCH)
     __asm__ __volatile__ ("" : : : "memory");
-#elif powerpc_HOST_ARCH || powerpc64_HOST_ARCH || powerpc64le_HOST_ARCH
+#elif defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
+    || defined(powerpc64le_HOST_ARCH)
     __asm__ __volatile__ ("lwsync" : : : "memory");
-#elif sparc_HOST_ARCH
+#elif defined(sparc_HOST_ARCH)
     /* Sparc in TSO mode does not require load/load barriers. */
     __asm__ __volatile__ ("" : : : "memory");
-#elif arm_HOST_ARCH
+#elif defined(arm_HOST_ARCH)
     __asm__ __volatile__ ("dmb" : : : "memory");
-#elif aarch64_HOST_ARCH
+#elif defined(aarch64_HOST_ARCH)
     __asm__ __volatile__ ("dmb sy" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
diff --git a/libraries/ghci/GHCi/ObjLink.hs b/libraries/ghci/GHCi/ObjLink.hs
index d7dbdd33736185d8d48c798c642c3ca83dde9dc7..3adb7ebaf9a1a72c145068cb87caddb497047b39 100644
--- a/libraries/ghci/GHCi/ObjLink.hs
+++ b/libraries/ghci/GHCi/ObjLink.hs
@@ -187,7 +187,7 @@ cLeadingUnderscore = False
 #endif
 
 isWindowsHost :: Bool
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
 isWindowsHost = True
 #else
 isWindowsHost = False
diff --git a/mk/warnings.mk b/mk/warnings.mk
index 5ca097f17ba8b75c03dacb230203a34bdca1d9b7..3c4c26d218fcd37540310e978d7eca8947773bbf 100644
--- a/mk/warnings.mk
+++ b/mk/warnings.mk
@@ -8,8 +8,8 @@ SRC_HC_OPTS     += -Wall
 # isn't supported yet (https://ghc.haskell.org/trac/ghc/wiki/Design/Warnings).
 #
 # See Note [Stage number in build variables] in mk/config.mk.in.
-SRC_HC_OPTS_STAGE1 += $(WERROR)
-SRC_HC_OPTS_STAGE2 += $(WERROR)
+SRC_HC_OPTS_STAGE1 += $(WERROR) -Wcpp-undef
+SRC_HC_OPTS_STAGE2 += $(WERROR) -Wcpp-undef
 
 
 ifneq "$(GccIsClang)" "YES"
diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h
index 16fbab2b2980adf39fcccd96a793278f11ab202a..a04db77b925fe943a44b6fb7d98df5ae3e4a2ba1 100644
--- a/rts/LinkerInternals.h
+++ b/rts/LinkerInternals.h
@@ -91,7 +91,8 @@ typedef struct ForeignExportStablePtr_ {
     struct ForeignExportStablePtr_ *next;
 } ForeignExportStablePtr;
 
-#if powerpc_HOST_ARCH || x86_64_HOST_ARCH || arm_HOST_ARCH
+#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) \
+    || defined(arm_HOST_ARCH)
 /* ios currently uses adjacent got tables, and no symbol extras */
 #if !defined(ios_HOST_OS)
 #define NEED_SYMBOL_EXTRAS 1
@@ -102,17 +103,17 @@ typedef struct ForeignExportStablePtr_ {
  * address relocations on the PowerPC, x86_64 and ARM.
  */
 typedef struct {
-#ifdef powerpc_HOST_ARCH
+#if defined(powerpc_HOST_ARCH)
     struct {
         short lis_r12, hi_addr;
         short ori_r12_r12, lo_addr;
         long mtctr_r12;
         long bctr;
     } jumpIsland;
-#elif x86_64_HOST_ARCH
+#elif defined(x86_64_HOST_ARCH)
     uint64_t    addr;
     uint8_t     jumpIsland[6];
-#elif arm_HOST_ARCH
+#elif defined(arm_HOST_ARCH)
     uint8_t     jumpIsland[16];
 #endif
 } SymbolExtra;
@@ -283,7 +284,7 @@ ObjectCode* mkOc( pathchar *path, char *image, int imageSize,
                   int misalignment
                   );
 
-#if defined (mingw32_HOST_OS)
+#if defined(mingw32_HOST_OS)
 /* We use myindex to calculate array addresses, rather than
    simply doing the normal subscript thing.  That's because
    some of the above structs have sizes which are not
diff --git a/rts/OldARMAtomic.c b/rts/OldARMAtomic.c
index 3c60e6d6699a136955901c1f8d615be5574ea1be..e76f4c63546617d2ff51f0c29dd9b072b7de2912 100644
--- a/rts/OldARMAtomic.c
+++ b/rts/OldARMAtomic.c
@@ -20,7 +20,7 @@
 #include <sched.h>
 #endif
 
-#if arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6)
+#if defined(arm_HOST_ARCH) && defined(arm_HOST_ARCH_PRE_ARMv6)
 
 static volatile int atomic_spin = 0;
 
diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm
index 4baf63a8f70409d1d0229a65f77f661babdc78d9..37eee439ac8a0c721f78a15848ebc21bc8878628 100644
--- a/rts/PrimOps.cmm
+++ b/rts/PrimOps.cmm
@@ -561,7 +561,7 @@ stg_atomicModifyMutVarzh ( gcptr mv, gcptr f )
          r = [stg_sel_1 z]   (max (HS + 1) MIN_UPD_SIZE)
     */
 
-#if MIN_UPD_SIZE > 1
+#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 1
 #define THUNK_1_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
 #define TICK_ALLOC_THUNK_1() TICK_ALLOC_UP_THK(WDS(1),WDS(MIN_UPD_SIZE-1))
 #else
@@ -569,7 +569,7 @@ stg_atomicModifyMutVarzh ( gcptr mv, gcptr f )
 #define TICK_ALLOC_THUNK_1() TICK_ALLOC_UP_THK(WDS(1),0)
 #endif
 
-#if MIN_UPD_SIZE > 2
+#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 2
 #define THUNK_2_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
 #define TICK_ALLOC_THUNK_2() TICK_ALLOC_UP_THK(WDS(2),WDS(MIN_UPD_SIZE-2))
 #else
diff --git a/rts/RtsUtils.c b/rts/RtsUtils.c
index 85f951addd89180b8583cf0b73f3e5155deeb8a4..996d28ac4c68eea7f0f9c714308564562b30496c 100644
--- a/rts/RtsUtils.c
+++ b/rts/RtsUtils.c
@@ -22,7 +22,7 @@
 /* HACK: On Mac OS X 10.4 (at least), time.h doesn't declare ctime_r with
  *       _POSIX_C_SOURCE. If this is the case, we declare it ourselves.
  */
-#if HAVE_CTIME_R && !HAVE_DECL_CTIME_R
+#if defined(HAVE_CTIME_R) && !HAVE_DECL_CTIME_R
 extern char *ctime_r(const time_t *, char *);
 #endif
 
@@ -164,7 +164,7 @@ time_str(void)
 
     if (now == 0) {
         time(&now);
-#if HAVE_CTIME_R
+#if defined(HAVE_CTIME_R)
         ctime_r(&now, nowstr);
 #else
         strcpy(nowstr, ctime(&now));
diff --git a/rts/Schedule.c b/rts/Schedule.c
index b77e7a21efe5c256ce0c1c74b3d782e4fa4d3cf6..296461b38db522a0d21d3111542f4ee890725eb4 100644
--- a/rts/Schedule.c
+++ b/rts/Schedule.c
@@ -411,7 +411,7 @@ run_thread:
     prev_what_next = t->what_next;
 
     errno = t->saved_errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
     SetLastError(t->saved_winerror);
 #endif
 
@@ -490,7 +490,7 @@ run_thread:
     // XXX: possibly bogus for SMP because this thread might already
     // be running again, see code below.
     t->saved_errno = errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
     // Similarly for Windows error code
     t->saved_winerror = GetLastError();
 #endif
@@ -2374,12 +2374,12 @@ suspendThread (StgRegTable *reg, bool interruptible)
   int saved_errno;
   StgTSO *tso;
   Task *task;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
   StgWord32 saved_winerror;
 #endif
 
   saved_errno = errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
   saved_winerror = GetLastError();
 #endif
 
@@ -2419,7 +2419,7 @@ suspendThread (StgRegTable *reg, bool interruptible)
   RELEASE_LOCK(&cap->lock);
 
   errno = saved_errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
   SetLastError(saved_winerror);
 #endif
   return task;
@@ -2433,12 +2433,12 @@ resumeThread (void *task_)
     Capability *cap;
     Task *task = task_;
     int saved_errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
     StgWord32 saved_winerror;
 #endif
 
     saved_errno = errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
     saved_winerror = GetLastError();
 #endif
 
@@ -2475,7 +2475,7 @@ resumeThread (void *task_)
     cap->r.rCurrentTSO = tso;
     cap->in_haskell = true;
     errno = saved_errno;
-#if mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
     SetLastError(saved_winerror);
 #endif
 
diff --git a/rts/Threads.c b/rts/Threads.c
index f5eb9d360cab0eed14fbdf50188ed12f7d177ffa..9cfd36a7c9ad1adbe923566a9811af720650f0ac 100644
--- a/rts/Threads.c
+++ b/rts/Threads.c
@@ -826,7 +826,7 @@ loop:
  * Debugging: why is a thread blocked
  * ------------------------------------------------------------------------- */
 
-#if DEBUG
+#ifdef DEBUG
 void
 printThreadBlockage(StgTSO *tso)
 {
diff --git a/rts/ghc.mk b/rts/ghc.mk
index b756d942ca1e4dfe4e8be1178cc51f3b392bb3c0..e24e199598770b416b183d568cb04f93710378fc 100644
--- a/rts/ghc.mk
+++ b/rts/ghc.mk
@@ -267,7 +267,10 @@ WARNING_OPTS += -Waggregate-return
 WARNING_OPTS += -Wpointer-arith
 WARNING_OPTS += -Wmissing-noreturn
 WARNING_OPTS += -Wnested-externs
-WARNING_OPTS += -Wredundant-decls 
+WARNING_OPTS += -Wredundant-decls
+ifeq "$(GccLT46)" "NO"
+WARNING_OPTS += -Wundef
+endif
 
 # These ones are hard to avoid:
 #WARNING_OPTS += -Wconversion
diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c
index 16b712a8045320958a18db74a99ce16ccef2fa4d..a7c9189250780251e22777e16e19c4ee99c8723c 100644
--- a/rts/linker/MachO.c
+++ b/rts/linker/MachO.c
@@ -248,7 +248,8 @@ ocVerifyImage_MachO(ObjectCode * oc)
 
     IF_DEBUG(linker, debugBelch("ocVerifyImage_MachO: start\n"));
 
-#if x86_64_HOST_ARCH || powerpc64_HOST_ARCH || aarch64_HOST_ARCH
+#if defined(x86_64_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
+    || defined(aarch64_HOST_ARCH)
     if(header->magic != MH_MAGIC_64) {
         errorBelch("Could not load image %s: bad magic!\n"
                    "  Expected %08x (64bit), got %08x%s\n",
@@ -281,7 +282,7 @@ resolveImports(
 
     IF_DEBUG(linker, debugBelch("resolveImports: start\n"));
 
-#if i386_HOST_ARCH
+#if defined(i386_HOST_ARCH)
     int isJumpTable = 0;
 
     if (strcmp(sect->sectname,"__jump_table") == 0) {
@@ -319,7 +320,7 @@ resolveImports(
         }
         ASSERT(addr);
 
-#if i386_HOST_ARCH
+#if defined(i386_HOST_ARCH)
         if (isJumpTable) {
             checkProddableBlock(oc,oc->image + sect->offset + i*itemSize, 5);
 
@@ -1922,7 +1923,8 @@ machoGetMisalignment( FILE * f )
     }
     fseek(f, -sizeof(header), SEEK_CUR);
 
-#if x86_64_HOST_ARCH || powerpc64_HOST_ARCH || aarch64_HOST_ARCH
+#if defined(x86_64_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
+    || defined(aarch64_HOST_ARCH)
     if(header.magic != MH_MAGIC_64) {
         barf("Bad magic. Expected: %08x, got: %08x.",
              MH_MAGIC_64, header.magic);
diff --git a/rts/posix/GetTime.c b/rts/posix/GetTime.c
index 4d257959483d0ddcb1050e5b1aacdad807d23716..5be9c8e3504b50aa79b5769c9245379c6a27c138 100644
--- a/rts/posix/GetTime.c
+++ b/rts/posix/GetTime.c
@@ -190,7 +190,7 @@ void getUnixEpochTime(StgWord64 *sec, StgWord32 *nsec)
 W_
 getPageFaults(void)
 {
-#if !defined(HAVE_GETRUSAGE) || haiku_HOST_OS
+#if !defined(HAVE_GETRUSAGE) || defined(haiku_HOST_OS)
     return 0;
 #else
     struct rusage t;
diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c
index dcf734f19d77068d6ad1954ab227fbdda0dfa479..48b154fa115a039cd8873418a5a3bba348135bf7 100644
--- a/rts/posix/OSMem.c
+++ b/rts/posix/OSMem.c
@@ -39,7 +39,7 @@
 
 #include <errno.h>
 
-#if darwin_HOST_OS || ios_HOST_OS
+#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
 #include <mach/mach.h>
 #include <mach/vm_map.h>
 #include <sys/sysctl.h>
@@ -114,7 +114,7 @@ my_mmap (void *addr, W_ size, int operation)
 {
     void *ret;
 
-#if darwin_HOST_OS
+#ifdef darwin_HOST_OS
     // Without MAP_FIXED, Apple's mmap ignores addr.
     // With MAP_FIXED, it overwrites already mapped regions, whic
     // mmap(0, ... MAP_FIXED ...) is worst of all: It unmaps the program text
@@ -170,9 +170,9 @@ my_mmap (void *addr, W_ size, int operation)
     else
         flags = 0;
 
-#if hpux_HOST_OS
+#ifdef hpux_HOST_OS
     ret = mmap(addr, size, prot, flags | MAP_ANONYMOUS | MAP_PRIVATE, -1, 0);
-#elif linux_HOST_OS
+#elif defined(linux_HOST_OS)
     ret = mmap(addr, size, prot, flags | MAP_ANON | MAP_PRIVATE, -1, 0);
     if (ret == (void *)-1 && errno == EPERM) {
         // Linux may return EPERM if it tried to give us
diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c
index 45f394208f0c2e73817f11148f1b53d2a2f1a3b2..465c8675a32a84a1ce5de8a663bdb87fd87d2867 100644
--- a/rts/posix/OSThreads.c
+++ b/rts/posix/OSThreads.c
@@ -137,7 +137,7 @@ createOSThread (OSThreadId* pId, char *name STG_UNUSED,
   int result = pthread_create(pId, NULL, (void *(*)(void *))startProc, param);
   if (!result) {
     pthread_detach(*pId);
-#if HAVE_PTHREAD_SETNAME_NP
+#ifdef HAVE_PTHREAD_SETNAME_NP
     pthread_setname_np(*pId, name);
 #endif
   }
diff --git a/rts/posix/itimer/Pthread.c b/rts/posix/itimer/Pthread.c
index 3b31fe4103af568eb1b01f7ac58ca5564212b3a8..5c708ecf4d84a791a47d81201de095dbc0e1a71c 100644
--- a/rts/posix/itimer/Pthread.c
+++ b/rts/posix/itimer/Pthread.c
@@ -65,7 +65,7 @@
 #include <unistd.h>
 #include <fcntl.h>
 
-#if HAVE_SYS_TIMERFD_H
+#ifdef HAVE_SYS_TIMERFD_H
 #include <sys/timerfd.h>
 #define USE_TIMERFD_FOR_ITIMER 1
 #else
@@ -101,7 +101,7 @@ static void *itimer_thread_func(void *_handle_tick)
     uint64_t nticks;
     int timerfd = -1;
 
-#if USE_TIMERFD_FOR_ITIMER
+#if defined(USE_TIMERFD_FOR_ITIMER) && USE_TIMERFD_FOR_ITIMER
     struct itimerspec it;
     it.it_value.tv_sec  = TimeToSeconds(itimer_interval);
     it.it_value.tv_nsec = TimeToNS(itimer_interval) % 1000000000;
@@ -169,7 +169,7 @@ initTicker (Time interval, TickProc handle_tick)
      * to the thread we create so we can later join to it if requested
      */
     if (! pthread_create(&thread, NULL, itimer_thread_func, (void*)handle_tick)) {
-#if HAVE_PTHREAD_SETNAME_NP
+#ifdef HAVE_PTHREAD_SETNAME_NP
         pthread_setname_np(thread, "ghc_ticker");
 #endif
     } else {
diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c
index 624dba30b234c8db80b7f5db2e182dac02f674a4..af90718b4fdcd9954a6bcdd40a0ba00c2ebbd201 100644
--- a/rts/sm/CNF.c
+++ b/rts/sm/CNF.c
@@ -1170,7 +1170,7 @@ compactFixupPointers(StgCompactNFData *str,
     dbl_link_onto(bd, &g0->compact_objects);
     RELEASE_SM_LOCK;
 
-#if DEBUG
+#ifdef DEBUG
     if (root)
         verify_consistency_loop(str);
 #endif
diff --git a/rts/sm/GCUtils.c b/rts/sm/GCUtils.c
index 9fda2fe07047c85af3ce583a7e62f7d218d92131..3717faebed6e3818fb24f9b5f7b7d5eb0ab554c9 100644
--- a/rts/sm/GCUtils.c
+++ b/rts/sm/GCUtils.c
@@ -346,7 +346,7 @@ alloc_todo_block (gen_workspace *ws, uint32_t size)
  * Debugging
  * -------------------------------------------------------------------------- */
 
-#if DEBUG
+#ifdef DEBUG
 void
 printMutableList(bdescr *bd)
 {
diff --git a/rts/sm/GCUtils.h b/rts/sm/GCUtils.h
index 3092262af63451597ef066318e664354c8cd4597..3ea762376a0256af243e4376423f2db998be3399 100644
--- a/rts/sm/GCUtils.h
+++ b/rts/sm/GCUtils.h
@@ -52,7 +52,7 @@ isPartiallyFull(bdescr *bd)
 }
 
 
-#if DEBUG
+#ifdef DEBUG
 void printMutableList (bdescr *bd);
 #endif
 
diff --git a/rts/sm/MBlock.c b/rts/sm/MBlock.c
index f6640d173c6dc069f3f7599cec7424726702391c..833dd8c7c2b77e4eeb561f55b4b759fd7cde3129 100644
--- a/rts/sm/MBlock.c
+++ b/rts/sm/MBlock.c
@@ -657,7 +657,7 @@ initMBlocks(void)
 #ifdef USE_LARGE_ADDRESS_SPACE
     {
         W_ size;
-#if aarch64_HOST_ARCH
+#ifdef aarch64_HOST_ARCH
         size = (W_)1 << 38; // 1/4 TByte
 #else
         size = (W_)1 << 40; // 1 TByte