From ff2c0cc9886a2c29958ee249e8eab45424001f77 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simon.peytonjones@gmail.com>
Date: Wed, 7 Feb 2024 12:19:35 +0000
Subject: [PATCH] Remove a dead comment

Just remove an out of date block of commented-out code, and tidy up
the relevant Notes.  See #8317.
---
 compiler/GHC/Core/Opt/ConstantFold.hs       | 13 +++----
 compiler/GHC/Core/Opt/Simplify/Iteration.hs | 40 ---------------------
 compiler/GHC/StgToCmm/Expr.hs               | 20 ++++-------
 testsuite/tests/linters/notes.stdout        |  1 -
 4 files changed, 13 insertions(+), 61 deletions(-)

diff --git a/compiler/GHC/Core/Opt/ConstantFold.hs b/compiler/GHC/Core/Opt/ConstantFold.hs
index f17e61d54262..a06db85798dd 100644
--- a/compiler/GHC/Core/Opt/ConstantFold.hs
+++ b/compiler/GHC/Core/Opt/ConstantFold.hs
@@ -3518,7 +3518,7 @@ tx_con_dtt _ alt = pprPanic "caseRules/dataToTag: bad alt" (ppr alt)
 {- Note [caseRules for tagToEnum]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 We want to transform
-   case tagToEnum x of
+   case tagToEnum# x of
      False -> e1
      True  -> e2
 into
@@ -3526,13 +3526,13 @@ into
      0# -> e1
      1# -> e2
 
-This rule eliminates a lot of boilerplate. For
+See #8317.   This rule eliminates a lot of boilerplate. For
   if (x>y) then e2 else e1
 we generate
-  case tagToEnum (x ># y) of
+  case tagToEnum# (x ># y) of
     False -> e1
     True  -> e2
-and it is nice to then get rid of the tagToEnum.
+and it is nice to then get rid of the tagToEnum#.
 
 Beware (#14768): avoid the temptation to map constructor 0 to
 DEFAULT, in the hope of getting this
@@ -3550,8 +3550,9 @@ We don't want to get this!
       DEFAULT -> e1
       DEFAULT -> e2
 
-Instead, we deal with turning one branch into DEFAULT in GHC.Core.Opt.Simplify.Utils
-(add_default in mkCase3).
+Instead, when possible, we turn one branch into DEFAULT in
+GHC.Core.Opt.Simplify.Utils.mkCase2; see Note [Literal cases]
+in that module.
 
 Note [caseRules for dataToTag]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Core/Opt/Simplify/Iteration.hs b/compiler/GHC/Core/Opt/Simplify/Iteration.hs
index 40f7f9d12a5c..a8827457de80 100644
--- a/compiler/GHC/Core/Opt/Simplify/Iteration.hs
+++ b/compiler/GHC/Core/Opt/Simplify/Iteration.hs
@@ -2510,27 +2510,6 @@ tryRules env rules fn args call_cont
   | null rules
   = return Nothing
 
-{- Disabled until we fix #8326
-  | fn `hasKey` tagToEnumKey   -- See Note [Optimising tagToEnum#]
-  , [_type_arg, val_arg] <- args
-  , Select dup bndr ((_,[],rhs1) : rest_alts) se cont <- call_cont
-  , isDeadBinder bndr
-  = do { let enum_to_tag :: CoreAlt -> CoreAlt
-                -- Takes   K -> e  into   tagK# -> e
-                -- where tagK# is the tag of constructor K
-             enum_to_tag (DataAlt con, [], rhs)
-               = assert (isEnumerationTyCon (dataConTyCon con) )
-                (LitAlt tag, [], rhs)
-              where
-                tag = mkLitInt (sePlatform env) (toInteger (dataConTag con - fIRST_TAG))
-             enum_to_tag alt = pprPanic "tryRules: tagToEnum" (ppr alt)
-
-             new_alts = (DEFAULT, [], rhs1) : map enum_to_tag rest_alts
-             new_bndr = setIdType bndr intPrimTy
-                 -- The binder is dead, but should have the right type
-      ; return (Just (val_arg, Select dup new_bndr new_alts se cont)) }
--}
-
   | Just (rule, rule_rhs) <- lookupRule ropts (getUnfoldingInRuleMatch env)
                                         (activeRule (seMode env)) fn
                                         (argInfoAppArgs args) rules
@@ -2706,25 +2685,6 @@ Note [OccInfo in unfoldings and rules] in GHC.Core.  There is something
 unsatisfactory about doing it twice; but the rule RHS is usually very
 small, and this is simple.
 
-Note [Optimising tagToEnum#]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-If we have an enumeration data type:
-
-  data Foo = A | B | C
-
-Then we want to transform
-
-   case tagToEnum# x of   ==>    case x of
-     A -> e1                       DEFAULT -> e1
-     B -> e2                       1#      -> e2
-     C -> e3                       2#      -> e3
-
-thereby getting rid of the tagToEnum# altogether.  If there was a DEFAULT
-alternative we retain it (remember it comes first).  If not the case must
-be exhaustive, and we reflect that in the transformed version by adding
-a DEFAULT.  Otherwise Lint complains that the new case is not exhaustive.
-See #8317.
-
 Note [Rules for recursive functions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 You might think that we shouldn't apply rules for a loop breaker:
diff --git a/compiler/GHC/StgToCmm/Expr.hs b/compiler/GHC/StgToCmm/Expr.hs
index a859c5df6dcc..a765a9e797de 100644
--- a/compiler/GHC/StgToCmm/Expr.hs
+++ b/compiler/GHC/StgToCmm/Expr.hs
@@ -234,6 +234,8 @@ start of each alternative.  Of course we certainly have to do so if
 the case forces an evaluation, or if there is a primitive op which can
 trigger GC.
 
+NB: things are not settled here: see #8326.
+
 A more interesting situation is this (a Plan-B situation)
 
         !P!;
@@ -652,20 +654,10 @@ cgCase scrut bndr alt_type alts
 
 {- Note [GC for conditionals]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-For boolean conditionals it seems that we have always done NoGcInAlts.
-That is, we have always done the GC check before the conditional.
-This is enshrined in the special case for
-   case tagToEnum# (a>b) of ...
-See Note [case on bool]
-
-It's odd, and it's flagrantly inconsistent with the rules described
-Note [Compiling case expressions].  However, after eliminating the
-tagToEnum# (#13397) we will have:
-   case (a>b) of ...
-Rather than make it behave quite differently, I am testing for a
-comparison operator here in the general case as well.
-
-ToDo: figure out what the Right Rule should be.
+For comparison operators (`is_cmp_op`) it seems that we have always done
+NoGcInAlts.  It's odd, and it's flagrantly inconsistent with the rules described
+Note [Compiling case expressions].  However, that's the way it has been for ages
+(there was some long-gone history involving tagToEnum#; see #13397, #8317, #8326).
 
 Note [scrut sequel]
 ~~~~~~~~~~~~~~~~~~~
diff --git a/testsuite/tests/linters/notes.stdout b/testsuite/tests/linters/notes.stdout
index 22ba864f939e..3374fb949146 100644
--- a/testsuite/tests/linters/notes.stdout
+++ b/testsuite/tests/linters/notes.stdout
@@ -16,7 +16,6 @@ ref    compiler/GHC/Hs/Pat.hs:141:74:     Note [Lifecycle of a splice]
 ref    compiler/GHC/HsToCore/Pmc/Solver.hs:856:20:     Note [COMPLETE sets on data families]
 ref    compiler/GHC/HsToCore/Quote.hs:1487:7:     Note [How brackets and nested splices are handled]
 ref    compiler/GHC/Stg/Unarise.hs:438:32:     Note [Renaming during unarisation]
-ref    compiler/GHC/StgToCmm/Expr.hs:578:4:     Note [case on bool]
 ref    compiler/GHC/Tc/Gen/HsType.hs:556:56:     Note [Skolem escape prevention]
 ref    compiler/GHC/Tc/Gen/HsType.hs:2676:7:     Note [Matching a kind signature with a declaration]
 ref    compiler/GHC/Tc/Gen/Pat.hs:174:20:     Note [Typing patterns in pattern bindings]
-- 
GitLab