diff --git a/System/Posix/Resource.hsc b/System/Posix/Resource.hsc
index a909a3498744768d64e69e8eab37e4bb9aaae9fc..8618ba7c7bdb096a9b03372b581a1a2194118859 100644
--- a/System/Posix/Resource.hsc
+++ b/System/Posix/Resource.hsc
@@ -1,5 +1,6 @@
 {-# LANGUAGE CApiFFI #-}
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  System.Posix.Resource
@@ -31,6 +32,9 @@ import Foreign.C
 import System.IO.Error ( ioeSetLocation )
 import GHC.IO.Exception ( unsupportedOperation )
 #endif
+#if __GLASGOW_HASKELL__ >= 905
+import GHC.Exts ( considerAccessible )
+#endif
 
 -- -----------------------------------------------------------------------------
 -- Resource limits
@@ -115,12 +119,20 @@ unpackRLimit :: CRLim -> ResourceLimit
 unpackRLimit (#const RLIM_INFINITY)  = ResourceLimitInfinity
 unpackRLimit other
 #if defined(RLIM_SAVED_MAX)
-    | ((#const RLIM_SAVED_MAX) :: CRLim) /= (#const RLIM_INFINITY) &&
-      other == (#const RLIM_SAVED_MAX) = ResourceLimitUnknown
+    | ((#const RLIM_SAVED_MAX) :: CRLim) /= (#const RLIM_INFINITY)
+    , other == (#const RLIM_SAVED_MAX)
+    = ResourceLimitUnknown
 #endif
 #if defined(RLIM_SAVED_CUR)
-    | ((#const RLIM_SAVED_CUR) :: CRLim) /= (#const RLIM_INFINITY) &&
-      other == (#const RLIM_SAVED_CUR) = ResourceLimitUnknown
+    | ((#const RLIM_SAVED_CUR) :: CRLim) /= (#const RLIM_INFINITY)
+    , other == (#const RLIM_SAVED_CUR)
+#if __GLASGOW_HASKELL__ >= 905
+    , considerAccessible
+#endif
+    = ResourceLimitUnknown
+    -- (*) This pattern match is redundant if RLIM_SAVED_MAX and RLIM_SAVED_CUR
+    -- are both defined and are equal. This redundancy is only detected by GHC
+    -- starting from version 9.5, so we use 'considerAccessible'.
 #endif
     | otherwise = ResourceLimit (fromIntegral other)