[Git][ghc/ghc][master] Improve heap overflow exception message (#25198)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Oct 24 05:24:02 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)
Catch heap overflow exceptions and suggest using `+RTS -M<size>`.
Fix #25198
- - - - -
5 changed files:
- compiler/GHC.hs
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/rts/T25198/T25198.hs
- + testsuite/tests/rts/T25198/T25198.stderr
- + testsuite/tests/rts/T25198/all.T
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -483,6 +483,8 @@ defaultErrorHandler fm (FlushOut flushOut) inner =
liftIO $ throwIO UserInterrupt
Just StackOverflow ->
fm "stack overflow: use +RTS -K<size> to increase it"
+ Just HeapOverflow ->
+ fm "heap overflow: use +RTS -M<size> to increase maximum heap size"
_ -> case fromException exception of
Just (ex :: ExitCode) -> liftIO $ throwIO ex
_ ->
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -23,6 +23,8 @@ Language
Compiler
~~~~~~~~
+- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
+
GHCi
~~~~
=====================================
testsuite/tests/rts/T25198/T25198.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+import Control.Exception
+import Language.Haskell.TH
+
+-- Generate a very large number of declarations
+generateDecls :: Int -> Q [Dec]
+generateDecls n = mapM (\i -> valD (varP (mkName ("x" ++ show i))) (normalB [| i |]) []) [1..n]
+
+main :: IO ()
+main = do
+ $(generateDecls 1000000)
+ print x1
=====================================
testsuite/tests/rts/T25198/T25198.stderr
=====================================
@@ -0,0 +1 @@
+heap overflow: use +RTS -M<size> to increase maximum heap size
=====================================
testsuite/tests/rts/T25198/all.T
=====================================
@@ -0,0 +1,4 @@
+test('T25198',
+ normal,
+ compile_fail,
+ ['+RTS -M8M -RTS'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ab8d751aabe37a1c141615bc80e310d14ae3e17
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ab8d751aabe37a1c141615bc80e310d14ae3e17
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/20241024/755f1e26/attachment-0001.html>
More information about the ghc-commits
mailing list