From 0c4d0489a925b83287bb1a9d625250a24ecc8473 Mon Sep 17 00:00:00 2001
From: Javier Neira <atreyu.bbb@gmail.com>
Date: Sat, 2 Jul 2022 10:08:47 +0200
Subject: [PATCH] Print a warning when assertions are enabled (#8240)

* Print a warning when assertions are enabled.

Fixes #4377.

* Remove redundant imports

* Add changelog about

Co-authored-by: Mikhail Glushenkov <mikhail.glushenkov@gmail.com>
---
 cabal-install/main/Main.hs | 16 ++++++++++++++--
 changelog.d/pr-8240        | 10 ++++++++++
 2 files changed, 24 insertions(+), 2 deletions(-)
 create mode 100644 changelog.d/pr-8240

diff --git a/cabal-install/main/Main.hs b/cabal-install/main/Main.hs
index 8395651e6c..cce3742f7b 100644
--- a/cabal-install/main/Main.hs
+++ b/cabal-install/main/Main.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE CPP, ScopedTypeVariables #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -166,7 +166,7 @@ import System.IO                ( BufferMode(LineBuffering), hSetBuffering
 import System.Directory         ( doesFileExist, getCurrentDirectory
                                 , withCurrentDirectory)
 import Data.Monoid              (Any(..))
-import Control.Exception        (try)
+import Control.Exception        (AssertionFailed, assert, try)
 
 
 -- | Entry point
@@ -177,6 +177,10 @@ main = do
   -- Enable line buffering so that we can get fast feedback even when piped.
   -- This is especially important for CI and build systems.
   hSetBuffering stdout LineBuffering
+
+  -- Check whether assertions are enabled and print a warning in that case.
+  warnIfAssertionsAreEnabled
+
   -- If the locale encoding for CLI doesn't support all Unicode characters,
   -- printing to it may fail unless we relax the handling of encoding errors
   -- when writing to stderr and stdout.
@@ -185,6 +189,14 @@ main = do
   (args0, args1) <- break (== "--") <$> getArgs
   mainWorker =<< (++ args1) <$> expandResponse args0
 
+warnIfAssertionsAreEnabled :: IO ()
+warnIfAssertionsAreEnabled =
+  assert False (return ()) `catch`
+  (\(_e :: AssertionFailed) -> putStrLn assertionsEnabledMsg)
+  where
+    assertionsEnabledMsg =
+      "Warning: this is a debug build with assertions enabled."
+
 mainWorker :: [String] -> IO ()
 mainWorker args = do
   maybeScriptAndArgs <- case args of
diff --git a/changelog.d/pr-8240 b/changelog.d/pr-8240
new file mode 100644
index 0000000000..51722217ae
--- /dev/null
+++ b/changelog.d/pr-8240
@@ -0,0 +1,10 @@
+synopsis: Print a warning when assertions are enabled
+packages: cabal-install
+prs: #8240
+issues: #4377
+
+description: {
+
+- Now cabal-install executable will print a warning if assertions are enabled
+
+}
-- 
GitLab