[commit: ghc] master: Reduce default for -fmax-pmcheck-iterations from 1e7 to 2e6 (d2e05c6)
git at git.haskell.org
git at git.haskell.org
Sun Apr 10 21:39:51 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/d2e05c6bd0834421b0c48b3c4287fbe6ee889966/ghc
>---------------------------------------------------------------
commit d2e05c6bd0834421b0c48b3c4287fbe6ee889966
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sun Apr 10 19:13:16 2016 +0200
Reduce default for -fmax-pmcheck-iterations from 1e7 to 2e6
The commit 28f951edfe50ea5182065144340061ec326781f5 introduced the
`-fmax-pmcheck-iterations` flag and set the default limit to 1e7
iterations.
However, this value is still high enough that it can result GHC to
exhibit memory spikes beyond 1 GiB of RAM usage (heap profile showed
several `(:)`s, as well as `THUNK_2_0`, and `PmCon` during the memory
spikes)
A value of 2e6 seems to be a safer upper bound which still manages to
let the checker not run into the limit in most cases.
Test Plan: Validate, try building a few Hackage packages
Reviewers: austin, gkaracha, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2095
>---------------------------------------------------------------
d2e05c6bd0834421b0c48b3c4287fbe6ee889966
compiler/cmm/CmmOpt.hs | 6 ++++++
compiler/main/DynFlags.hs | 2 +-
compiler/nativeGen/X86/CodeGen.hs | 6 ++++++
compiler/prelude/PrimOp.hs | 5 +++++
compiler/types/OptCoercion.hs | 8 ++++++--
testsuite/tests/pmcheck/should_compile/T11195.hs | 1 +
6 files changed, 25 insertions(+), 3 deletions(-)
diff --git a/compiler/cmm/CmmOpt.hs b/compiler/cmm/CmmOpt.hs
index 7c634c2..de3061d 100644
--- a/compiler/cmm/CmmOpt.hs
+++ b/compiler/cmm/CmmOpt.hs
@@ -1,5 +1,11 @@
{-# LANGUAGE CPP #-}
+-- The default iteration limit is a bit too low for the definitions
+-- in this module.
+#if __GLASGOW_HASKELL__ >= 800
+{-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-}
+#endif
+
-----------------------------------------------------------------------------
--
-- Cmm optimisation
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 9e06445..a79bb3a 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -1445,7 +1445,7 @@ defaultDynFlags mySettings =
debugLevel = 0,
simplPhases = 2,
maxSimplIterations = 4,
- maxPmCheckIterations = 10000000,
+ maxPmCheckIterations = 2000000,
ruleCheck = Nothing,
maxRelevantBinds = Just 6,
simplTickFactor = 100,
diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index 2d22734..cd45d92 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -1,5 +1,11 @@
{-# LANGUAGE CPP, GADTs, NondecreasingIndentation #-}
+-- The default iteration limit is a bit too low for the definitions
+-- in this module.
+#if __GLASGOW_HASKELL__ >= 800
+{-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-}
+#endif
+
-----------------------------------------------------------------------------
--
-- Generating machine code (instruction selection)
diff --git a/compiler/prelude/PrimOp.hs b/compiler/prelude/PrimOp.hs
index 7b37062..be91ae6 100644
--- a/compiler/prelude/PrimOp.hs
+++ b/compiler/prelude/PrimOp.hs
@@ -6,6 +6,11 @@
{-# LANGUAGE CPP #-}
+-- The default is a bit too low for the quite large primOpInfo definition
+#if __GLASGOW_HASKELL__ >= 801
+{-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-}
+#endif
+
module PrimOp (
PrimOp(..), PrimOpVecCat(..), allThePrimOps,
primOpType, primOpSig,
diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs
index e39f0aa..ca67bc7 100644
--- a/compiler/types/OptCoercion.hs
+++ b/compiler/types/OptCoercion.hs
@@ -1,8 +1,12 @@
-- (c) The University of Glasgow 2006
{-# LANGUAGE CPP #-}
- -- This module used to take 10GB of memory to compile with the new
- -- (Nov '15) pattern-match checker.
+
+-- The default iteration limit is a bit too low for the definitions
+-- in this module.
+#if __GLASGOW_HASKELL__ >= 800
+{-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-}
+#endif
module OptCoercion ( optCoercion, checkAxInstCo ) where
diff --git a/testsuite/tests/pmcheck/should_compile/T11195.hs b/testsuite/tests/pmcheck/should_compile/T11195.hs
index 593223f..236932e 100644
--- a/testsuite/tests/pmcheck/should_compile/T11195.hs
+++ b/testsuite/tests/pmcheck/should_compile/T11195.hs
@@ -1,4 +1,5 @@
{-# OPTIONS_GHC -Woverlapping-patterns -Wincomplete-patterns #-}
+{-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-}
module T11195 where
More information about the ghc-commits
mailing list