[Git][ghc/ghc][wip/T22739] compiler: Small optimisation of assertM

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Mon Jan 16 17:01:34 UTC 2023



Ben Gamari pushed to branch wip/T22739 at Glasgow Haskell Compiler / GHC


Commits:
4e17ebb1 by Ben Gamari at 2023-01-16T12:01:29-05:00
compiler: Small optimisation of assertM

In #22739 @AndreasK noticed that assertM performed the action to compute
the asserted predicate regardless of whether DEBUG is enabled. This is
inconsistent with the other assertion operations and general convention.
Fix this.

Closes #22739.

- - - - -


1 changed file:

- compiler/GHC/Utils/Panic/Plain.hs


Changes:

=====================================
compiler/GHC/Utils/Panic/Plain.hs
=====================================
@@ -29,6 +29,8 @@ import GHC.Utils.Constants
 import GHC.Utils.Exception as Exception
 import GHC.Stack
 import GHC.Prelude.Basic
+
+import Control.Monad (when)
 import System.IO.Unsafe
 
 -- | This type is very similar to 'GHC.Utils.Panic.GhcException', but it omits
@@ -150,4 +152,8 @@ massert cond = withFrozenCallStack (assert cond (pure ()))
 
 assertM :: (HasCallStack, Monad m) => m Bool -> m ()
 {-# INLINE assertM #-}
-assertM mcond = withFrozenCallStack (mcond >>= massert)
+assertM mcond
+  | debugIsOn = withFrozenCallStack $ do
+      res <- mcond
+      when (not res) assertPanic'
+  | otherwise = return ()



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e17ebb1872f1b0ec7868abe0e92c11b9effd910

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e17ebb1872f1b0ec7868abe0e92c11b9effd910
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230116/a834f42d/attachment-0001.html>


More information about the ghc-commits mailing list