[Git][ghc/ghc][master] Eta-expand the Simplifier monad

Marge Bot gitlab at gitlab.haskell.org
Tue Jul 28 00:10:26 UTC 2020



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


Commits:
3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00
Eta-expand the Simplifier monad

This patch eta-expands the Simplifier's monad, using the method
explained in GHC.Core.Unify Note [The one-shot state monad trick].
It's part of the exta-expansion programme in #18202.

It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated
by the compiler.  Here's the list, based on the compiler-performance
tests in perf/compiler:

                    Reduction in bytes allocated
   T10858(normal)      -0.7%
   T12425(optasm)      -1.3%
   T13056(optasm)      -1.8%
   T14683(normal)      -1.1%
   T15164(normal)      -1.3%
   T15630(normal)      -1.4%
   T17516(normal)      -2.3%
   T18282(normal)      -1.6%
   T18304(normal)      -0.8%
   T1969(normal)       -0.6%
   T4801(normal)       -0.8%
   T5321FD(normal)     -0.7%
   T5321Fun(normal)    -0.5%
   T5642(normal)       -0.9%
   T6048(optasm)       -1.1%
   T9020(optasm)       -2.7%
   T9233(normal)       -0.7%
   T9675(optasm)       -0.5%
   T9961(normal)       -2.9%
   WWRec(normal)       -1.2%

Metric Decrease:
    T12425
    T9020
    T9961

- - - - -


1 changed file:

- compiler/GHC/Core/Opt/Simplify/Monad.hs


Changes:

=====================================
compiler/GHC/Core/Opt/Simplify/Monad.hs
=====================================
@@ -43,6 +43,7 @@ import GHC.Utils.Panic     (throwGhcExceptionIO, GhcException (..))
 import GHC.Types.Basic     ( IntWithInf, treatZeroAsInf, mkIntWithInf )
 import Control.Monad       ( ap )
 import GHC.Core.Multiplicity        ( pattern Many )
+import GHC.Exts( oneShot )
 
 {-
 ************************************************************************
@@ -56,14 +57,25 @@ For the simplifier monad, we want to {\em thread} a unique supply and a counter.
 -}
 
 newtype SimplM result
-  =  SM  { unSM :: SimplTopEnv  -- Envt that does not change much
-                -> UniqSupply   -- We thread the unique supply because
-                                -- constantly splitting it is rather expensive
-                -> SimplCount
-                -> IO (result, UniqSupply, SimplCount)}
-  -- we only need IO here for dump output
+  =  SM'  { unSM :: SimplTopEnv  -- Envt that does not change much
+                 -> UniqSupply   -- We thread the unique supply because
+                                 -- constantly splitting it is rather expensive
+                 -> SimplCount
+                 -> IO (result, UniqSupply, SimplCount)}
+    -- We only need IO here for dump output
     deriving (Functor)
 
+pattern SM :: (SimplTopEnv -> UniqSupply -> SimplCount
+               -> IO (result, UniqSupply, SimplCount))
+          -> SimplM result
+-- This pattern synonym makes the simplifier monad eta-expand,
+-- which as a very beneficial effect on compiler performance
+-- (worth a 1-2% reduction in bytes-allocated).  See #18202.
+-- See Note [The one-shot state monad trick] in GHC.Core.Unify
+pattern SM m <- SM' m
+  where
+    SM m = SM' (oneShot m)
+
 data SimplTopEnv
   = STE { st_flags     :: DynFlags
         , st_max_ticks :: IntWithInf  -- Max #ticks in this simplifier run



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3d345c9680ab3d766ef43dd8389ccc1eaeca066c
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/20200727/42e6c5a1/attachment-0001.html>


More information about the ghc-commits mailing list