Skip to content

Commit

Permalink
Make -frewrite-rules into a dynamic flag; off for -O0
Browse files Browse the repository at this point in the history
Argubly rewrite rules should not fire with -O0, and it turns
out that when compiling GHC.Base with -O0 we get a crash if
the rewrite rules do fire (see Note [Scoping for Builtin rules]
in PrelRules).

So unless someone yells, rewrite rules are off with -O0.

The new (now dynamic) flag is 
    -frewrite rules (with -fno-rewrite-rules to disable)

The old (static) flag -frules-off is gone.
  • Loading branch information
simonpj@microsoft.com committed May 4, 2007
1 parent 6f1d589 commit 5943ce9
Show file tree
Hide file tree
Showing 7 changed files with 86 additions and 42 deletions.
2 changes: 1 addition & 1 deletion compiler/deSugar/DsListComp.lhs
Expand Up @@ -50,7 +50,7 @@ dsListComp lquals body elt_ty
let
quals = map unLoc lquals
in
if opt_RulesOff || dopt Opt_IgnoreInterfacePragmas dflags
if not (dopt Opt_RewriteRules dflags) || dopt Opt_IgnoreInterfacePragmas dflags
-- Either rules are switched off, or we are ignoring what there are;
-- Either way foldr/build won't happen, so use the more efficient
-- Wadler-style desugaring
Expand Down
8 changes: 7 additions & 1 deletion compiler/main/DynFlags.hs
Expand Up @@ -192,6 +192,7 @@ data DynFlag
| Opt_CaseMerge
| Opt_UnboxStrictFields
| Opt_DictsCheap
| Opt_RewriteRules

-- misc opts
| Opt_Cpp
Expand Down Expand Up @@ -560,12 +561,16 @@ optLevelFlags :: [([Int], DynFlag)]
optLevelFlags
= [ ([0], Opt_IgnoreInterfacePragmas)
, ([0], Opt_OmitInterfacePragmas)

, ([1,2], Opt_IgnoreAsserts)
, ([1,2], Opt_RewriteRules) -- Off for -O0; see Note [Scoping for Builtin rules]
-- in PrelRules
, ([1,2], Opt_DoEtaReduction)
, ([1,2], Opt_CaseMerge)
, ([1,2], Opt_Strictness)
, ([1,2], Opt_CSE)
, ([1,2], Opt_FullLaziness)

, ([2], Opt_LiberateCase)
, ([2], Opt_SpecConstr)

Expand Down Expand Up @@ -1067,7 +1072,8 @@ fFlags = [
( "asm-mangling", Opt_DoAsmMangling ),
( "print-bind-result", Opt_PrintBindResult ),
( "force-recomp", Opt_ForceRecomp ),
( "hpc-no-auto", Opt_Hpc_No_Auto )
( "hpc-no-auto", Opt_Hpc_No_Auto ),
( "rewrite-rules", Opt_RewriteRules )
]


Expand Down
3 changes: 0 additions & 3 deletions compiler/main/StaticFlags.hs
Expand Up @@ -42,7 +42,6 @@ module StaticFlags (
opt_NoMethodSharing,
opt_NoStateHack,
opt_CprOff,
opt_RulesOff,
opt_SimplNoPreInlining,
opt_SimplExcessPrecision,
opt_MaxWorkerArgs,
Expand Down Expand Up @@ -296,7 +295,6 @@ opt_Flatten = lookUp FSLIT("-fflatten")
opt_NoStateHack = lookUp FSLIT("-fno-state-hack")
opt_NoMethodSharing = lookUp FSLIT("-fno-method-sharing")
opt_CprOff = lookUp FSLIT("-fcpr-off")
opt_RulesOff = lookUp FSLIT("-frules-off")
-- Switch off CPR analysis in the new demand analyser
opt_MaxWorkerArgs = lookup_def_int "-fmax-worker-args" (10::Int)

Expand Down Expand Up @@ -369,7 +367,6 @@ isStaticFlag f =
"static",
"funregisterised",
"fext-core",
"frules-off",
"fcpr-off",
"ferror-spans",
"fPIC"
Expand Down
31 changes: 28 additions & 3 deletions compiler/prelude/PrelRules.lhs
Expand Up @@ -44,9 +44,7 @@ import Name ( Name, nameOccName )
import Outputable
import FastString
import StaticFlags ( opt_SimplExcessPrecision )
import Data.Bits as Bits ( Bits(..), shiftL, shiftR )
-- shiftL and shiftR were not always methods of Bits
import Data.Bits as Bits
import Data.Word ( Word )
\end{code}

Expand Down Expand Up @@ -447,6 +445,33 @@ dataToTagRule other = Nothing
%* *
%************************************************************************
Note [Scoping for Builtin rules]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When compiling a (base-package) module that defines one of the
functions mentioned in the RHS of a built-in rule, there's a danger
that we'll see
f = ...(eq String x)....
....and lower down...
eqString = ...
Then a rewrite would give
f = ...(eqString x)...
....and lower down...
eqString = ...
and lo, eqString is not in scope. This only really matters when we get to code
generation. With -O we do a GlomBinds step that does a new SCC analysis on the whole
set of bindings, which sorts out the dependency. Without -O we don't do any rule
rewriting so again we are fine.
(This whole thing doesn't show up for non-built-in rules because their dependencies
are explicit.)
\begin{code}
builtinRules :: [CoreRule]
-- Rules for non-primops that can't be expressed using a RULE pragma
Expand Down
7 changes: 4 additions & 3 deletions compiler/simplCore/SimplUtils.lhs
Expand Up @@ -774,10 +774,11 @@ activeInline env id
where
prag = idInlinePragma id
activeRule :: SimplEnv -> Maybe (Activation -> Bool)
activeRule :: DynFlags -> SimplEnv -> Maybe (Activation -> Bool)
-- Nothing => No rules at all
activeRule env
| opt_RulesOff = Nothing
activeRule dflags env
| not (dopt Opt_RewriteRules dflags)
= Nothing -- Rewriting is off
| otherwise
= case getMode env of
SimplGently -> Just isAlwaysActive
Expand Down
2 changes: 1 addition & 1 deletion compiler/simplCore/Simplify.lhs
Expand Up @@ -967,7 +967,7 @@ completeCall env var cont
-- So it's up to the programmer: rules can cause divergence
; let in_scope = getInScope env
rules = getRules env
maybe_rule = case activeRule env of
maybe_rule = case activeRule dflags env of
Nothing -> Nothing -- No rules apply
Just act_fn -> lookupRule act_fn in_scope
rules var args
Expand Down
75 changes: 45 additions & 30 deletions docs/users_guide/flags.xml
Expand Up @@ -928,7 +928,7 @@
<tbody>
<row>
<entry><option>-fcase-merge</option></entry>
<entry>Enable case-merging</entry>
<entry>Enable case-merging. Implied by <option>-O</option>.</entry>
<entry>dynamic</entry>
<entry><option>-fno-case-merge</option></entry>
</row>
Expand All @@ -942,7 +942,7 @@

<row>
<entry><option>-fdo-eta-reduction</option></entry>
<entry>Enable eta-reduction</entry>
<entry>Enable eta-reduction. Implied by <option>-O</option>.</entry>
<entry>dynamic</entry>
<entry><option>-fno-do-eta-reduction</option></entry>
</row>
Expand All @@ -961,14 +961,6 @@
<entry><option>-fno-excess-precision</option></entry>
</row>

<row>
<entry><option>-frules-off</option></entry>
<entry>Switch off all rewrite rules (including rules
generated by automatic specialisation of overloaded functions)</entry>
<entry>static</entry>
<entry><option>-frules-off</option></entry>
</row>

<row>
<entry><option>-fignore-asserts</option></entry>
<entry>Ignore assertions in the source</entry>
Expand All @@ -983,13 +975,6 @@
<entry><option>-fno-ignore-interface-pragmas</option></entry>
</row>

<row>
<entry><option>-fliberate-case-threshold</option></entry>
<entry>Tweak the liberate-case optimisation (default: 10)</entry>
<entry>static</entry>
<entry><option>-fno-liberate-case-threshold</option></entry>
</row>

<row>
<entry><option>-fomit-interface-pragmas</option></entry>
<entry>Don't generate interface pragmas</entry>
Expand Down Expand Up @@ -1021,31 +1006,54 @@
</row>

<row>
<entry><option>-fno-cse</option></entry>
<entry>Turn off common sub-expression</entry>
<entry><option>-fcse</option></entry>
<entry>Turn on common sub-expression elimination. Implied by <option>-O</option>.</entry>
<entry>dynamic</entry>
<entry>-</entry>
<entry>-fno-cse</entry>
</row>

<row>
<entry><option>-fno-full-laziness</option></entry>
<entry>Turn off full laziness (floating bindings outwards).</entry>
<entry><option>-ffull-laziness</option></entry>
<entry>Turn on full laziness (floating bindings outwards). Implied by <option>-O</option>.</entry>
<entry>dynamic</entry>
<entry>-ffull-laziness</entry>
<entry>-fno-full-laziness</entry>
</row>

<row>
<entry><option>-fno-pre-inlining</option></entry>
<entry>Turn off pre-inlining</entry>
<entry>static</entry>
<entry>-</entry>
<entry><option>-frewrite-rules</option></entry>
<entry>Switch on all rewrite rules (including rules
generated by automatic specialisation of overloaded functions).
Implied by <option>-O</option>. </entry>
<entry>dynamic</entry>
<entry><option>-fno-rewrite-rules</option></entry>
</row>

<row>
<entry><option>-fno-strictness</option></entry>
<entry>Turn off strictness analysis</entry>
<entry><option>-fstrictness</option></entry>
<entry>Turn on strictness analysis. Implied by <option>-O</option>.</entry>
<entry>dynamic</entry>
<entry>-</entry>
<entry>-fno-strictness</entry>
</row>

<row>
<entry><option>-fspec-constr</option></entry>
<entry>Turn on the SpecConstr transformation. Implied by <option>-O2</option>.</entry>
<entry>dynamic</entry>
<entry>-fno-spec-constr</entry>
</row>

<row>
<entry><option>-fliberate-case</option></entry>
<entry>Turn on the liberate-case transformation. Implied by <option>-O2</option>.</entry>
<entry>dynamic</entry>
<entry>-fno-liberate-case</entry>
</row>

<row>
<entry><option>-fliberate-case-threshold</option></entry>
<entry>Tweak the liberate-case optimisation (default: 10)</entry>
<entry>static</entry>
<entry><option>-fno-liberate-case-threshold</option></entry>
</row>

<row>
Expand Down Expand Up @@ -1089,6 +1097,13 @@
<entry>static</entry>
<entry><option>-fno-unfolding-use-threshold</option></entry>
</row>

<row>
<entry><option>-fno-pre-inlining</option></entry>
<entry>Turn off pre-inlining</entry>
<entry>static</entry>
<entry>-</entry>
</row>
</tbody>
</tgroup>
</informaltable>
Expand Down

0 comments on commit 5943ce9

Please sign in to comment.