diff --git a/Control/Concurrent/STM/TArray.hs b/Control/Concurrent/STM/TArray.hs
index 4ac2db4f9e81326d09b7dbbef2b6cf274e719d3b..2bce54552c59fbf18a82eaa897667f25c4752c47 100644
--- a/Control/Concurrent/STM/TArray.hs
+++ b/Control/Concurrent/STM/TArray.hs
@@ -4,9 +4,11 @@
 {-# LANGUAGE Trustworthy #-}
 #endif
 
-#define HAS_UNLIFTED_ARRAY defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 904
+#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 904
+#define HAS_UNLIFTED_ARRAY 1
+#endif
 
-#if HAS_UNLIFTED_ARRAY
+#if defined(HAS_UNLIFTED_ARRAY)
 {-# LANGUAGE MagicHash, UnboxedTuples #-}
 #endif
 
@@ -30,7 +32,7 @@ module Control.Concurrent.STM.TArray (
 
 import Control.Monad.STM (STM, atomically)
 import Data.Typeable (Typeable)
-#if HAS_UNLIFTED_ARRAY
+#if defined(HAS_UNLIFTED_ARRAY)
 import Control.Concurrent.STM.TVar (readTVar, readTVarIO, writeTVar)
 import Data.Array.Base (safeRangeSize, MArray(..))
 import Data.Ix (Ix)
@@ -47,7 +49,7 @@ import Data.Array.Base (safeRangeSize, unsafeAt, MArray(..), IArray(numElements)
 -- interface for mutable arrays.
 --
 -- It is conceptually implemented as @Array i (TVar e)@.
-#if HAS_UNLIFTED_ARRAY
+#if defined(HAS_UNLIFTED_ARRAY)
 data TArray i e = TArray
     !i   -- lower bound
     !i   -- upper bound
diff --git a/changelog.md b/changelog.md
index ec40e66dfdaabab24a56b35af796ac6590850284..7bb017b845057c03d9d63075dd61040f6789f21c 100644
--- a/changelog.md
+++ b/changelog.md
@@ -1,5 +1,9 @@
 # Changelog for [`stm` package](http://hackage.haskell.org/package/stm)
 
+## 2.5.2.1 *September 2023*
+
+  * Eliminate reliance on undefined CPP behavior ([#75](https://github.com/haskell/stm/issues/75))
+
 ## 2.5.2.0 *September 2023*
 
   * Fix strictness of `stateTVar` ([#30](https://github.com/haskell/stm/ssues/30))