Fix flaggery for RULES (cf Trac #2497)
authorsimonpj@microsoft.com <unknown>
Tue, 26 Aug 2008 12:21:21 +0000 (12:21 +0000)
committersimonpj@microsoft.com <unknown>
Tue, 26 Aug 2008 12:21:21 +0000 (12:21 +0000)
This patch executes the plan described in the discussion in Trac #2497.
Specficially:

    * Inside a RULE, switch on the forall-as-keyword in the lexer,
      unconditionally. (Actually this is done by an earlier patch.)

    * Merge the -XScopedTypeVariables and -XPatternSignatures flags,
      and deprecate the latter. Distinguishing them isn't senseless,
      but it's jolly confusing.

    * Inside a RULE, switch on -XScopedTypeVariables unconditionally.

    * Change -frewrite-rules to -fenable-rewrite-rules; deprecate the former.
      Internally the DynFlag is now Opt_EnableRewriteRules.

There's a test in typecheck/should_compile/T2497.hs

compiler/deSugar/DsExpr.lhs
compiler/deSugar/DsListComp.lhs
compiler/ghc.cabal
compiler/main/DynFlags.hs
compiler/rename/RnPat.lhs
compiler/rename/RnSource.lhs
compiler/simplCore/SimplUtils.lhs
compiler/typecheck/TcDeriv.lhs
docs/users_guide/flags.xml
docs/users_guide/glasgow_exts.xml

index eed7f87..f152ff5 100644 (file)
@@ -564,7 +564,7 @@ dsExplicitList :: PostTcType -> [LHsExpr Id] -> DsM CoreExpr
 dsExplicitList elt_ty xs = do
     dflags <- getDOptsDs
     xs' <- mapM dsLExpr xs
-    if not (dopt Opt_RewriteRules dflags)
+    if not (dopt Opt_EnableRewriteRules dflags)
         then return $ mkListExpr elt_ty xs'
         else mkBuildExpr elt_ty (mkSplitExplicitList (thisPackage dflags) xs')
   where
index 2bd1a6d..bdbe65e 100644 (file)
@@ -56,7 +56,7 @@ dsListComp lquals body elt_ty = do
     dflags <- getDOptsDs
     let quals = map unLoc lquals
     
-    if not (dopt Opt_RewriteRules dflags) || dopt Opt_IgnoreInterfacePragmas dflags
+    if not (dopt Opt_EnableRewriteRules 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
index b1de64e..437ebc2 100644 (file)
@@ -85,7 +85,7 @@ Library
     Extensions: CPP, MagicHash, UnboxedTuples, PatternGuards,
                 ForeignFunctionInterface, EmptyDataDecls,
                 TypeSynonymInstances, MultiParamTypeClasses,
-                FlexibleInstances, Rank2Types, PatternSignatures
+                FlexibleInstances, Rank2Types, ScopedTypeVariables
 
     Include-Dirs: . parser utils
 
index 062443d..a3330e7 100644 (file)
@@ -229,7 +229,6 @@ data DynFlag
    | Opt_MagicHash
    | Opt_EmptyDataDecls
    | Opt_KindSignatures
-   | Opt_PatternSignatures
    | Opt_ParallelListComp
    | Opt_TransformListComp
    | Opt_GeneralizedNewtypeDeriving
@@ -261,7 +260,7 @@ data DynFlag
    | Opt_UnboxStrictFields
    | Opt_MethodSharing
    | Opt_DictsCheap
-   | Opt_RewriteRules
+   | Opt_EnableRewriteRules            -- Apply rewrite rules during simplification
    | Opt_Vectorise
    | Opt_RegsGraph                      -- do graph coloring register allocation
    | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
@@ -794,8 +793,8 @@ optLevelFlags
     , ([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_EnableRewriteRules)  -- Off for -O0; see Note [Scoping for Builtin rules]
+                                         --              in PrelRules
     , ([1,2],   Opt_DoEtaReduction)
     , ([1,2],   Opt_CaseMerge)
     , ([1,2],   Opt_Strictness)
@@ -1470,6 +1469,12 @@ deprecatedForLanguage lang turn_on
       flag | turn_on    = lang
            | otherwise = "No"++lang
 
+useInstead :: String -> Bool -> Deprecated
+useInstead flag turn_on
+  = Deprecated ("Use -f" ++ no ++ flag ++ " instead")
+  where
+    no = if turn_on then "" else "no-"
+
 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
 fFlags = [
@@ -1518,7 +1523,8 @@ fFlags = [
   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, const Supported ),
-  ( "rewrite-rules",                    Opt_RewriteRules, const Supported ),
+  ( "rewrite-rules",                    Opt_EnableRewriteRules, useInstead "enable-rewrite-rules" ),
+  ( "enable-rewrite-rules",             Opt_EnableRewriteRules, const Supported ),
   ( "break-on-exception",               Opt_BreakOnException, const Supported ),
   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
@@ -1583,7 +1589,6 @@ xFlags = [
   ( "PolymorphicComponents",            Opt_PolymorphicComponents, const Supported ),
   ( "ExistentialQuantification",        Opt_ExistentialQuantification, const Supported ),
   ( "KindSignatures",                   Opt_KindSignatures, const Supported ),
-  ( "PatternSignatures",                Opt_PatternSignatures, const Supported ),
   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, const Supported ),
   ( "ParallelListComp",                 Opt_ParallelListComp, const Supported ),
   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
@@ -1620,6 +1625,11 @@ xFlags = [
   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, const Supported ),
+
+  -- -XPatternSignatures is deprecated; now -XScopedTypeVariables enables pattern signatures  
+  ( "PatternSignatures",                Opt_ScopedTypeVariables, 
+    deprecatedForLanguage "ScopedTypeVariables" ),
+
   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
@@ -1675,7 +1685,6 @@ glasgowExtsFlags = [
            , Opt_ParallelListComp
            , Opt_EmptyDataDecls
            , Opt_KindSignatures
-           , Opt_PatternSignatures
            , Opt_GeneralizedNewtypeDeriving
            , Opt_TypeFamilies ]
 
index 584c287..18f3dd5 100644 (file)
@@ -212,7 +212,7 @@ rnLPatAndThen var@(NM varf) (L loc p) cont =
                -- (e.g. in the pattern (x, x -> y) x needs to be bound in the rhs of the tuple)
                                      
          SigPatIn pat ty -> do
-             patsigs <- doptM Opt_PatternSignatures
+             patsigs <- doptM Opt_ScopedTypeVariables
              if patsigs
               then rnLPatAndThen var pat
                       (\ pat' -> do { (ty', fvs1) <- rnHsTypeFVs tvdoc ty
@@ -580,7 +580,7 @@ checkTupSize tup_size
 patSigErr :: Outputable a => a -> SDoc
 patSigErr ty
   =  (ptext (sLit "Illegal signature in pattern:") <+> ppr ty)
-       $$ nest 4 (ptext (sLit "Use -XPatternSignatures to permit it"))
+       $$ nest 4 (ptext (sLit "Use -XScopedTypeVariables to permit it"))
 
 dupFieldErr :: String -> RdrName -> SDoc
 dupFieldErr str dup
index 27de40f..cebc674 100644 (file)
@@ -174,7 +174,9 @@ rnSrcDecls shadowP group@(HsGroup {hs_valds  = val_decls,
    -- (H) Rename Everything else
 
    (rn_inst_decls,    src_fvs2) <- rnList rnSrcInstDecl   inst_decls ;
-   (rn_rule_decls,    src_fvs3) <- rnList rnHsRuleDecl    rule_decls ;
+   (rn_rule_decls,    src_fvs3) <- setOptM Opt_ScopedTypeVariables $
+                                  rnList rnHsRuleDecl    rule_decls ;
+                          -- Inside RULES, scoped type variables are on
    (rn_foreign_decls, src_fvs4) <- rnList rnHsForeignDecl foreign_decls ;
    (rn_default_decls, src_fvs5) <- rnList rnDefaultDecl   default_decls ;
    (rn_deriv_decls,   src_fvs6) <- rnList rnSrcDerivDecl  deriv_decls ;
index be5c4b3..1fdde7f 100644 (file)
@@ -797,7 +797,7 @@ activeInline env id
 activeRule :: DynFlags -> SimplEnv -> Maybe (Activation -> Bool)
 -- Nothing => No rules at all
 activeRule dflags env
-  | not (dopt Opt_RewriteRules dflags)
+  | not (dopt Opt_EnableRewriteRules dflags)
   = Nothing    -- Rewriting is off
   | otherwise
   = case getMode env of
index efc46cd..ea38b34 100644 (file)
@@ -308,8 +308,8 @@ renameDeriv is_boot gen_binds insts
 
   | otherwise
   = discardWarnings $   -- Discard warnings about unused bindings etc
-    do { (rn_gen, dus_gen) <- setOptM Opt_PatternSignatures $  -- Type signatures in patterns 
-                                                               -- are used in the generic binds
+    do { (rn_gen, dus_gen) <- setOptM Opt_ScopedTypeVariables $  -- Type signatures in patterns 
+                                                                 -- are used in the generic binds
                               rnTopBinds (ValBindsIn gen_binds [])
        ; keepAliveSetTc (duDefs dus_gen)       -- Mark these guys to be kept alive
 
index 32eb565..5e52d61 100644 (file)
              <entry><option>-XNoKindSignatures</option></entry>
            </row>
            <row>
-             <entry><option>-XPatternSignatures</option></entry>
-             <entry>Enable <link linkend="pattern-type-sigs">pattern type signatures</link>.</entry>
-             <entry>dynamic</entry>
-             <entry><option>-XNoPatternSignatures</option></entry>
-           </row>
-           <row>
              <entry><option>-XEmptyDataDecls</option></entry>
              <entry>Enable empty data declarations.</entry>
              <entry>dynamic</entry>
index 1484815..0bccb9e 100644 (file)
@@ -6674,15 +6674,7 @@ data S = S {-# UNPACK #-} !Int {-# UNPACK #-} !Int
 
 <para>
 The programmer can specify rewrite rules as part of the source program
-(in a pragma).  GHC applies these rewrite rules wherever it can, provided (a) 
-the <option>-O</option> flag (<xref linkend="options-optimise"/>) is on, 
-and (b) the <option>-fno-rewrite-rules</option> flag
-(<xref linkend="options-f"/>) is not specified, and (c) the
-<option>-fglasgow-exts</option> (<xref linkend="options-language"/>)
-flag is active.
-</para>
-
-<para>
+(in a pragma).  
 Here is an example:
 
 <programlisting>
@@ -6802,17 +6794,40 @@ variables it mentions, though of course they need to be in scope.
 <listitem>
 
 <para>
- Rules are automatically exported from a module, just as instance declarations are.
+ All rules are implicitly exported from the module, and are therefore
+in force in any module that imports the module that defined the rule, directly
+or indirectly.  (That is, if A imports B, which imports C, then C's rules are
+in force when compiling A.)  The situation is very similar to that for instance
+declarations.
 </para>
 </listitem>
 
+<listitem>
+
+<para>
+Inside a RULE "<literal>forall</literal>" is treated as a keyword, regardless of
+any other flag settings.  Furthermore, inside a RULE, the language extension
+<option>-XScopedTypeVariables</option> is automatically enabled; see 
+<xref linkend="scoped-type-variables"/>.
+</para>
+</listitem>
+<listitem>
+
+<para>
+Like other pragmas, RULE pragmas are always checked for scope errors, and
+are typechecked. Typechecking means that the LHS and RHS of a rule are typechecked, 
+and must have the same type.  However, rules are only <emphasis>enabled</emphasis>
+if the <option>-fenable-rewrite-rules</option> flag is 
+on (see <xref linkend="rule-semantics"/>).
+</para>
+</listitem>
 </itemizedlist>
 
 </para>
 
 </sect2>
 
-<sect2>
+<sect2 id="rule-semantics">
 <title>Semantics</title>
 
 <para>
@@ -6820,9 +6835,17 @@ From a semantic point of view:
 
 <itemizedlist>
 <listitem>
-
 <para>
-Rules are only applied if you use the <option>-O</option> flag.
+Rules are enabled (that is, used during optimisation)
+by the <option>-fenable-rewrite-rules</option> flag.
+This flag is implied by <option>-O</option>, and may be switched
+off (as usual) by <option>-fno-enable-rewrite-rules</option>.
+(NB: enabling <option>-fenable-rewrite-rules</option> without <option>-O</option> 
+may not do what you expect, though, because without <option>-O</option> GHC 
+ignores all optimisation information in interface files;
+see <option>-fignore-interface-pragmas</option>, <xref linkend="options-f"/>.)
+Note that <option>-fenable-rewrite-rules</option> is an <emphasis>optimisation</emphasis> flag, and
+has no effect on parsing or typechecking.
 </para>
 </listitem>
 
@@ -6839,14 +6862,6 @@ expression by substituting for the pattern variables.
 <listitem>
 
 <para>
- The LHS and RHS of a rule are typechecked, and must have the
-same type.
-
-</para>
-</listitem>
-<listitem>
-
-<para>
  GHC makes absolutely no attempt to verify that the LHS and RHS
 of a rule have the same meaning.  That is undecidable in general, and
 infeasible in most interesting cases.  The responsibility is entirely the programmer's!
@@ -6939,17 +6954,6 @@ pragma on <literal>f</literal>, to ensure
 that it is not inlined until its RULEs have had a chance to fire.
 </para>
 </listitem>
-<listitem>
-
-<para>
- All rules are implicitly exported from the module, and are therefore
-in force in any module that imports the module that defined the rule, directly
-or indirectly.  (That is, if A imports B, which imports C, then C's rules are
-in force when compiling A.)  The situation is very similar to that for instance
-declarations.
-</para>
-</listitem>
-
 </itemizedlist>
 
 </para>