[commit: ghc] wip/validate-ci: Revert "Disable binder swap in OccurAnal (Trac #16288)" (f903a5b)

git at git.haskell.org git at git.haskell.org
Thu Feb 21 15:13:35 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/validate-ci
Link       : http://ghc.haskell.org/trac/ghc/changeset/f903a5b5ba6ef9de569a814c8d6e351ab99c336c/ghc

>---------------------------------------------------------------

commit f903a5b5ba6ef9de569a814c8d6e351ab99c336c
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Thu Feb 21 13:52:57 2019 +0000

    Revert "Disable binder swap in OccurAnal (Trac #16288)"
    
    This reverts commit 9049bfb1773cf114fd4e2d2d6daed46af2b73093.
    
    This causes a core lint error, see #16346


>---------------------------------------------------------------

f903a5b5ba6ef9de569a814c8d6e351ab99c336c
 compiler/coreSyn/CoreUnfold.hs                     | 43 +++-------------------
 .../dependent/should_compile/dynamic-paper.stderr  |  4 +-
 .../tests/simplCore/should_compile/T16288A.hs      | 17 ---------
 .../tests/simplCore/should_compile/T16288B.hs      |  7 ----
 .../tests/simplCore/should_compile/T16288C.hs      | 13 -------
 testsuite/tests/simplCore/should_compile/all.T     |  1 -
 6 files changed, 7 insertions(+), 78 deletions(-)

diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs
index 3ac35c9..11c2a75 100644
--- a/compiler/coreSyn/CoreUnfold.hs
+++ b/compiler/coreSyn/CoreUnfold.hs
@@ -47,7 +47,7 @@ import GhcPrelude
 import DynFlags
 import CoreSyn
 import PprCore          ()      -- Instances
-import OccurAnal        ( occurAnalyseExpr_NoBinderSwap )
+import OccurAnal        ( occurAnalyseExpr )
 import CoreOpt
 import CoreArity       ( manifestArity )
 import CoreUtils
@@ -101,7 +101,7 @@ mkDFunUnfolding :: [Var] -> DataCon -> [CoreExpr] -> Unfolding
 mkDFunUnfolding bndrs con ops
   = DFunUnfolding { df_bndrs = bndrs
                   , df_con = con
-                  , df_args = map occurAnalyseExpr_NoBinderSwap ops }
+                  , df_args = map occurAnalyseExpr ops }
                   -- See Note [Occurrence analysis of unfoldings]
 
 mkWwInlineRule :: DynFlags -> CoreExpr -> Arity -> Unfolding
@@ -311,7 +311,7 @@ mkCoreUnfolding :: UnfoldingSource -> Bool -> CoreExpr
                 -> UnfoldingGuidance -> Unfolding
 -- Occurrence-analyses the expression before capturing it
 mkCoreUnfolding src top_lvl expr guidance
-  = CoreUnfolding { uf_tmpl         = occurAnalyseExpr_NoBinderSwap expr,
+  = CoreUnfolding { uf_tmpl         = occurAnalyseExpr expr,
                       -- See Note [Occurrence analysis of unfoldings]
                     uf_src          = src,
                     uf_is_top       = top_lvl,
@@ -330,7 +330,7 @@ mkUnfolding :: DynFlags -> UnfoldingSource
 -- Calculates unfolding guidance
 -- Occurrence-analyses the expression before capturing it
 mkUnfolding dflags src is_top_lvl is_bottoming expr
-  = CoreUnfolding { uf_tmpl         = occurAnalyseExpr_NoBinderSwap expr,
+  = CoreUnfolding { uf_tmpl         = occurAnalyseExpr expr,
                       -- See Note [Occurrence analysis of unfoldings]
                     uf_src          = src,
                     uf_is_top       = is_top_lvl,
@@ -342,7 +342,7 @@ mkUnfolding dflags src is_top_lvl is_bottoming expr
   where
     is_top_bottoming = is_top_lvl && is_bottoming
     guidance         = calcUnfoldingGuidance dflags is_top_bottoming expr
-        -- NB: *not* (calcUnfoldingGuidance (occurAnalyseExpr_NoBinderSwap expr))!
+        -- NB: *not* (calcUnfoldingGuidance (occurAnalyseExpr expr))!
         -- See Note [Calculate unfolding guidance on the non-occ-anal'd expression]
 
 {-
@@ -364,39 +364,6 @@ But more generally, the simplifier is designed on the
 basis that it is looking at occurrence-analysed expressions, so better
 ensure that they acutally are.
 
-We use occurAnalyseExpr_NoBinderSwap instead of occurAnalyseExpr;
-see Note [No binder swap in unfoldings].
-
-Note [No binder swap in unfoldings]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The binder swap can temporarily violate Core Lint, by assinging
-a LocalId binding to a GlobalId. For example, if A.foo{r872}
-is a GlobalId with unique r872, then
-
- case A.foo{r872} of bar {
-   K x -> ...(A.foo{r872})...
- }
-
-gets transformed to
-
-  case A.foo{r872} of bar {
-    K x -> let foo{r872} = bar
-           in ...(A.foo{r872})...
-
-This is usually not a problem, because the simplifier will transform
-this to:
-
-  case A.foo{r872} of bar {
-    K x -> ...(bar)...
-
-However, after occurrence analysis but before simplification, this extra 'let'
-violates the Core Lint invariant that we do not have local 'let' bindings for
-GlobalIds.  That seems (just) tolerable for the occurrence analysis that happens
-just before the Simplifier, but not for unfoldings, which are Linted
-independently.
-As a quick workaround, we disable binder swap in this module.
-See Trac #16288 and #16296 for further plans.
-
 Note [Calculate unfolding guidance on the non-occ-anal'd expression]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Notice that we give the non-occur-analysed expression to
diff --git a/testsuite/tests/dependent/should_compile/dynamic-paper.stderr b/testsuite/tests/dependent/should_compile/dynamic-paper.stderr
index a170d29..3ba4db2 100644
--- a/testsuite/tests/dependent/should_compile/dynamic-paper.stderr
+++ b/testsuite/tests/dependent/should_compile/dynamic-paper.stderr
@@ -1,5 +1,5 @@
 Simplifier ticks exhausted
-  When trying UnfoldingDone delta
+  When trying UnfoldingDone delta1
   To increase the limit, use -fsimpl-tick-factor=N (default 100).
    
   If you need to increase the limit substantially, please file a
@@ -12,4 +12,4 @@ Simplifier ticks exhausted
   simplifier non-termination has been judged acceptable.
    
   To see detailed counts use -ddump-simpl-stats
-  Total ticks: 140007
+  Total ticks: 140004
diff --git a/testsuite/tests/simplCore/should_compile/T16288A.hs b/testsuite/tests/simplCore/should_compile/T16288A.hs
deleted file mode 100644
index c6a52bf..0000000
--- a/testsuite/tests/simplCore/should_compile/T16288A.hs
+++ /dev/null
@@ -1,17 +0,0 @@
-module T16288A where
-
-import T16288C
-
-data License
-
-class Pretty a where
-  pretty :: a -> Doc
-
-instance Pretty License where
-  pretty _  = pretV
-
-bar :: (Pretty a) => a -> Doc
-bar w = foo (pretty (u w w w w))
-
-u :: a -> a -> a -> a -> a
-u = u
diff --git a/testsuite/tests/simplCore/should_compile/T16288B.hs b/testsuite/tests/simplCore/should_compile/T16288B.hs
deleted file mode 100644
index c1a98d2..0000000
--- a/testsuite/tests/simplCore/should_compile/T16288B.hs
+++ /dev/null
@@ -1,7 +0,0 @@
-module T16288B where
-
-import T16288A
-import T16288C
-
-bar2 :: License -> Doc
-bar2 = bar
diff --git a/testsuite/tests/simplCore/should_compile/T16288C.hs b/testsuite/tests/simplCore/should_compile/T16288C.hs
deleted file mode 100644
index 5efbb2e..0000000
--- a/testsuite/tests/simplCore/should_compile/T16288C.hs
+++ /dev/null
@@ -1,13 +0,0 @@
-module T16288C where
-
-data Doc = Empty | Beside Doc
-
-hcat :: Doc -> Doc
-hcat Empty = Empty
-hcat xs = hcat xs
-
-pretV = hcat Empty
-
-foo :: Doc -> Doc
-foo Empty = hcat Empty
-foo val = Beside val
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 6e1979c..170c206 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -300,4 +300,3 @@ test('T15631',
      normal,
      makefile_test, ['T15631'])
 test('T15673', normal, compile, ['-O'])
-test('T16288', normal, multimod_compile, ['T16288B', '-O -dcore-lint -v0'])



More information about the ghc-commits mailing list