[Git][ghc/ghc][master] Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Oct 10 23:01:17 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
e96c51cb by Andreas Klebinger at 2023-10-10T16:44:27+01:00
Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around.

The motivation for the flag is given in #21917.

- - - - -


8 changed files:

- compiler/GHC/Driver/Config/Tidy.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Tidy.hs
- docs/users_guide/using-optimisation.rst
- + testsuite/tests/simplCore/should_compile/T21917.hs
- + testsuite/tests/simplCore/should_compile/T21917.stderr
- testsuite/tests/simplCore/should_compile/all.T


Changes:

=====================================
compiler/GHC/Driver/Config/Tidy.hs
=====================================
@@ -40,6 +40,7 @@ initTidyOpts hsc_env = do
     , opt_expose_rules      = not (gopt Opt_OmitInterfacePragmas dflags)
     , opt_trim_ids          = gopt Opt_OmitInterfacePragmas dflags
     , opt_static_ptr_opts   = static_ptr_opts
+    , opt_keep_auto_rules   = gopt Opt_KeepAutoRules dflags
     }
 
 initStaticPtrOpts :: HscEnv -> IO StaticPtrOpts


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -323,6 +323,7 @@ data GeneralFlag
    | Opt_IgnoreInterfacePragmas
    | Opt_OmitInterfacePragmas
    | Opt_ExposeAllUnfoldings
+   | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless
    | Opt_WriteInterface -- forces .hi files to be written even with -fno-code
    | Opt_WriteHie -- generate .hie files
 


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2371,6 +2371,7 @@ fFlagsDeps = [
   flagSpec "error-spans"                      Opt_ErrorSpans,
   flagSpec "excess-precision"                 Opt_ExcessPrecision,
   flagSpec "expose-all-unfoldings"            Opt_ExposeAllUnfoldings,
+  flagSpec "keep-auto-rules"                  Opt_KeepAutoRules,
   flagSpec "expose-internal-symbols"          Opt_ExposeInternalSymbols,
   flagSpec "external-dynamic-refs"            Opt_ExternalDynamicRefs,
   flagSpec "external-interpreter"             Opt_ExternalInterpreter,


=====================================
compiler/GHC/Iface/Tidy.hs
=====================================
@@ -384,6 +384,7 @@ data TidyOpts = TidyOpts
       -- ^ Are rules exposed or not?
   , opt_static_ptr_opts :: !(Maybe StaticPtrOpts)
       -- ^ Options for generated static pointers, if enabled (/= Nothing).
+  , opt_keep_auto_rules :: !Bool
   }
 
 tidyProgram :: TidyOpts -> ModGuts -> IO (CgGuts, ModDetails)
@@ -418,6 +419,8 @@ tidyProgram opts (ModGuts { mg_module           = mod
     Nothing    -> pure ([], Nothing, tidy_binds)
     Just sopts -> sptCreateStaticBinds sopts mod tidy_binds
 
+  -- pprTraceM "trimmed_rules" (ppr trimmed_rules)
+
   let all_foreign_stubs = case mcstub of
         Nothing    -> foreign_stubs
         Just cstub -> foreign_stubs `appendStubC` cstub
@@ -989,12 +992,18 @@ called in the final code), we keep the rule too.
 
 This stuff is the only reason for the ru_auto field in a Rule.
 
-NB: In #18532 we looked at keeping auto-rules and it turned out to just make
-compiler performance worse while increasing code sizes at the same time. The impact
-varied. Compiling Cabal got ~3% slower, allocated ~3% more and wrote 15% more code to disk.
-Nofib only saw 0.7% more compiler allocations and executable file size growth. But given
-there was no difference in runtime for these benchmarks it turned out to be flat out worse.
-See the ticket for more details.
+We discard auto-rules by default, but keep them if -fkeep-auto-rules is on.
+
+* Discard by default: in #18532 we looked at keeping auto-rules and it turned out to just make
+  compiler performance worse while increasing code sizes at the same time. The
+  impact varied. Compiling Cabal got ~3% slower, allocated ~3% more and wrote 15%
+  more code to disk.  Nofib only saw 0.7% more compiler allocations and executable
+  file size growth. But given there was no difference in runtime for these
+  benchmarks it turned out to be flat out worse.  See the ticket for more details.
+
+* Keep with -fkeep-auto-rules: in #21917 we found cases where we get a lot code
+  duplication when we discard specialisations.  Agda is a case in point.  Having
+  a flag gives us control over the rule-trimming decision.
 -}
 
 findExternalRules :: TidyOpts
@@ -1006,11 +1015,12 @@ findExternalRules :: TidyOpts
 findExternalRules opts binds imp_id_rules unfold_env
   = (trimmed_binds, filter keep_rule all_rules)
   where
-    imp_rules | (opt_expose_rules opts) = filter expose_rule imp_id_rules
-              | otherwise               = []
+    imp_rules | opt_expose_rules opts = filter expose_rule imp_id_rules
+              | otherwise             = []
     imp_user_rule_fvs = mapUnionVarSet user_rule_rhs_fvs imp_rules
 
-    user_rule_rhs_fvs rule | isAutoRule rule = emptyVarSet
+    user_rule_rhs_fvs rule | isAutoRule rule && not (opt_keep_auto_rules opts)
+                                             = emptyVarSet
                            | otherwise       = ruleRhsFreeVars rule
 
     (trimmed_binds, local_bndrs, _, all_rules) = trim_binds binds
@@ -1071,7 +1081,7 @@ findExternalRules opts binds imp_id_rules unfold_env
             -- In needed_fvs', we don't bother to delete binders from the fv set
 
          local_rules  = [ rule
-                        | (opt_expose_rules opts)
+                        | opt_expose_rules opts
                         , id <- bndrs
                         , is_external_id id   -- Only collect rules for external Ids
                         , rule <- idCoreRules id


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -621,6 +621,24 @@ as such you shouldn't need to set any of them explicitly. A flag
     strictness information for a function, GHC will ignore that
     information.
 
+.. ghc-flag:: -fkeep-auto-rules
+    :shortdesc: Keep all "auto" rules, generated by specialisation
+    :type: dynamic
+    :reverse: -fno-keep-auto-rules
+    :category:
+
+    :default: off
+
+    The type-class specialiser and call-pattern specialisation both
+    generate so-called "auto" RULES.  These rules are usually exposed
+    to importing modules in the interface file. But an auto rule is the
+    sole reason for keeping a function alive, both the rule and the function
+    are discarded, by default. That reduces code bloat, but risks the same
+    function being specialised again in an importing module.
+
+    You can change this behaviour with :ghc-flag:`-fkeep-auto-rules`. Switching
+    it on keeps all auto-generated rules.
+
 .. ghc-flag:: -flate-dmd-anal
     :shortdesc: Run demand analysis again, at the end of the
         simplification pipeline


=====================================
testsuite/tests/simplCore/should_compile/T21917.hs
=====================================
@@ -0,0 +1,21 @@
+-- With -fkeep-auto-rules we should get an externally-visible
+-- specialisation.  See #21917
+--
+-- "SPEC foo @IO @Int"
+--     forall ($dMonad :: Monad IO) ($dIntegral :: Integral Int).
+--      foo1 @IO @Int $dMonad $dIntegral = foo_$sfoo
+
+module T21917 where
+
+{-# INLINABLE foo #-}
+foo :: (Monad m, Integral a) => a -> a -> a -> IO (a,a,a,a,a, m a)
+foo x y z = do
+  let !x1 = x+1
+  let !x2 = x+2
+  let !x3 = x+3
+  let !x4 = x+4
+  let !x5 = x+5
+  pure (x1, x2, x3, x4, x5, pure (x1+x2))
+
+bar :: Int -> IO (Int,Int,Int,Int,Int, IO Int)
+bar = foo 1 2


=====================================
testsuite/tests/simplCore/should_compile/T21917.stderr
=====================================
@@ -0,0 +1,8 @@
+
+==================== Tidy Core rules ====================
+"SPEC foo @IO @Int"
+    forall ($dMonad :: Monad IO) ($dIntegral :: Integral Int).
+      foo1 @IO @Int $dMonad $dIntegral
+      = foo_$sfoo
+
+


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -504,3 +504,5 @@ test('T23952', [extra_files(['T23952a.hs'])], multimod_compile, ['T23952', '-v0
 test('T24014', normal, compile, ['-dcore-lint'])
 test('T24029', normal, compile, [''])
 test('T21348', normal, compile, ['-O'])
+test('T21917', normal, compile, ['-O -fkeep-auto-rules -ddump-rules'])
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e96c51cbd137113ec953d8b7b0817d2d268f3c96

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e96c51cbd137113ec953d8b7b0817d2d268f3c96
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/20231010/ae388af9/attachment-0001.html>


More information about the ghc-commits mailing list