Skip to content
Snippets Groups Projects
Commit 2a6079a2 authored by sheaf's avatar sheaf Committed by Bodigrim
Browse files

Avoid redundant pattern warning in Resource.hsc

With GHC MR !8478, GHC is able to spot a redundant pattern match
when RLIM_SAVED_CUR == RLIM_SAVED_MAX, which it wasn't able to
detect before. So we use considerAccessible to avoid a pattern match
check. This unfortunately means we must change the SafeHaskell status
of that module to TrustWorth, as considerAccessible is from GHC.Exts,
which isn't safe.

Alternatives:

  - we can't perform the equality test RLIM_SAVED_CUR == RLIM_SAVED_MAX
    using CPP macros, because one of the values might expand out to
    have casts;
  - turning off pattern match warnings impacts warnings across the whole
    module, instead of the single affected function,
  - adding a dummy equation such as "id True" to the first pattern match
    would work, but seems more ad-hoc.
parent 70369061
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CApiFFI #-}
#if __GLASGOW_HASKELL__ >= 709
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
-----------------------------------------------------------------------------
-- |
-- Module : System.Posix.Resource
......@@ -31,6 +28,10 @@ import System.Posix.Types
import Foreign
import Foreign.C
#if __GLASGOW_HASKELL__ >= 905
import GHC.Exts ( considerAccessible )
#endif
-- -----------------------------------------------------------------------------
-- Resource limits
......@@ -100,12 +101,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)
......
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