[Git][ghc/ghc][wip/T23916] New line number in hard_hole_fits

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Wed Sep 13 13:34:08 UTC 2023



Simon Peyton Jones pushed to branch wip/T23916 at Glasgow Haskell Compiler / GHC


Commits:
f498a24e by Simon Peyton Jones at 2023-09-13T14:33:53+01:00
New line number in hard_hole_fits

- - - - -


1 changed file:

- testsuite/tests/perf/compiler/hard_hole_fits.stderr


Changes:

=====================================
testsuite/tests/perf/compiler/hard_hole_fits.stderr
=====================================
@@ -115,13 +115,14 @@ hard_hole_fits.hs:19:25: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:20:24: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:20:36: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
-    • In an equation for ‘testMe’: testMe (HsLam xl mg) = _
+    • In an equation for ‘testMe’: testMe (HsLam xlc lc_variant mg) = _
     • Relevant bindings include
         mg :: MatchGroup GhcPs (LHsExpr GhcPs)
-          (bound at hard_hole_fits.hs:20:18)
-        xl :: Language.Haskell.Syntax.Extension.XLam GhcPs
+          (bound at hard_hole_fits.hs:20:30)
+        lc_variant :: HsLamVariant (bound at hard_hole_fits.hs:20:19)
+        xlc :: Language.Haskell.Syntax.Extension.XLam GhcPs
           (bound at hard_hole_fits.hs:20:15)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
@@ -134,35 +135,14 @@ hard_hole_fits.hs:20:24: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:21:40: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
-    • Found hole: _ :: Int
-    • In an equation for ‘testMe’:
-          testMe (HsLamCase xlc lc_variant mg) = _
-    • Relevant bindings include
-        mg :: MatchGroup GhcPs (LHsExpr GhcPs)
-          (bound at hard_hole_fits.hs:21:34)
-        lc_variant :: LamCaseVariant (bound at hard_hole_fits.hs:21:23)
-        xlc :: Language.Haskell.Syntax.Extension.XLamCase GhcPs
-          (bound at hard_hole_fits.hs:21:19)
-        testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
-      Valid hole fits include
-        maxBound :: forall a. Bounded a => a
-          with maxBound @Int
-          (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
-           (and originally defined in ‘GHC.Enum’))
-        minBound :: forall a. Bounded a => a
-          with minBound @Int
-          (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
-           (and originally defined in ‘GHC.Enum’))
-
-hard_hole_fits.hs:22:28: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:21:28: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsApp xa gl gl') = _
     • Relevant bindings include
-        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:22:21)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:22:18)
+        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:21:21)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:21:18)
         xa :: Language.Haskell.Syntax.Extension.XApp GhcPs
-          (bound at hard_hole_fits.hs:22:15)
+          (bound at hard_hole_fits.hs:21:15)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -174,19 +154,19 @@ hard_hole_fits.hs:22:28: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:23:38: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:22:38: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’:
           testMe (HsAppType xate gl at hwcb) = _
     • Relevant bindings include
         hwcb :: Language.Haskell.Syntax.Type.LHsWcType
                   (Language.Haskell.Syntax.Extension.NoGhcTc GhcPs)
-          (bound at hard_hole_fits.hs:23:30)
+          (bound at hard_hole_fits.hs:22:30)
         at :: Language.Haskell.Syntax.Concrete.LHsToken "@" GhcPs
-          (bound at hard_hole_fits.hs:23:27)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:23:24)
+          (bound at hard_hole_fits.hs:22:27)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:22:24)
         xate :: Language.Haskell.Syntax.Extension.XAppTypeE GhcPs
-          (bound at hard_hole_fits.hs:23:19)
+          (bound at hard_hole_fits.hs:22:19)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -198,15 +178,15 @@ hard_hole_fits.hs:23:38: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:24:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:23:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (OpApp xoa gl gl' gl2) = _
     • Relevant bindings include
-        gl2 :: LHsExpr GhcPs (bound at hard_hole_fits.hs:24:26)
-        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:24:22)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:24:19)
+        gl2 :: LHsExpr GhcPs (bound at hard_hole_fits.hs:23:26)
+        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:23:22)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:23:19)
         xoa :: Language.Haskell.Syntax.Extension.XOpApp GhcPs
-          (bound at hard_hole_fits.hs:24:15)
+          (bound at hard_hole_fits.hs:23:15)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -218,14 +198,14 @@ hard_hole_fits.hs:24:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:25:29: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:24:29: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (NegApp xna gl se) = _
     • Relevant bindings include
-        se :: SyntaxExpr GhcPs (bound at hard_hole_fits.hs:25:23)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:25:20)
+        se :: SyntaxExpr GhcPs (bound at hard_hole_fits.hs:24:23)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:24:20)
         xna :: Language.Haskell.Syntax.Extension.XNegApp GhcPs
-          (bound at hard_hole_fits.hs:25:16)
+          (bound at hard_hole_fits.hs:24:16)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -237,17 +217,17 @@ hard_hole_fits.hs:25:29: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:26:30: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:25:30: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsPar xp gl ab ac) = _
     • Relevant bindings include
         ac :: Language.Haskell.Syntax.Concrete.LHsToken ")" GhcPs
-          (bound at hard_hole_fits.hs:26:24)
-        ab :: LHsExpr GhcPs (bound at hard_hole_fits.hs:26:21)
+          (bound at hard_hole_fits.hs:25:24)
+        ab :: LHsExpr GhcPs (bound at hard_hole_fits.hs:25:21)
         gl :: Language.Haskell.Syntax.Concrete.LHsToken "(" GhcPs
-          (bound at hard_hole_fits.hs:26:18)
+          (bound at hard_hole_fits.hs:25:18)
         xp :: Language.Haskell.Syntax.Extension.XPar GhcPs
-          (bound at hard_hole_fits.hs:26:15)
+          (bound at hard_hole_fits.hs:25:15)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -259,14 +239,14 @@ hard_hole_fits.hs:26:30: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:27:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:26:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (SectionL xsl gl gl') = _
     • Relevant bindings include
-        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:27:25)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:27:22)
+        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:26:25)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:26:22)
         xsl :: Language.Haskell.Syntax.Extension.XSectionL GhcPs
-          (bound at hard_hole_fits.hs:27:18)
+          (bound at hard_hole_fits.hs:26:18)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -278,14 +258,14 @@ hard_hole_fits.hs:27:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:28:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:27:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (SectionR xsr gl gl') = _
     • Relevant bindings include
-        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:28:25)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:28:22)
+        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:27:25)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:27:22)
         xsr :: Language.Haskell.Syntax.Extension.XSectionR GhcPs
-          (bound at hard_hole_fits.hs:28:18)
+          (bound at hard_hole_fits.hs:27:18)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -297,16 +277,16 @@ hard_hole_fits.hs:28:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:29:38: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:28:38: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’:
           testMe (ExplicitTuple xet gls box) = _
     • Relevant bindings include
         box :: Language.Haskell.Syntax.Basic.Boxity
-          (bound at hard_hole_fits.hs:29:31)
-        gls :: [HsTupArg GhcPs] (bound at hard_hole_fits.hs:29:27)
+          (bound at hard_hole_fits.hs:28:31)
+        gls :: [HsTupArg GhcPs] (bound at hard_hole_fits.hs:28:27)
         xet :: Language.Haskell.Syntax.Extension.XExplicitTuple GhcPs
-          (bound at hard_hole_fits.hs:29:23)
+          (bound at hard_hole_fits.hs:28:23)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -318,23 +298,23 @@ hard_hole_fits.hs:29:38: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:30:35: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:29:35: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (ExplicitSum xes n i gl) = _
     • Relevant bindings include
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:30:29)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:29:29)
         i :: Language.Haskell.Syntax.Basic.SumWidth
-          (bound at hard_hole_fits.hs:30:27)
+          (bound at hard_hole_fits.hs:29:27)
         n :: Language.Haskell.Syntax.Basic.ConTag
-          (bound at hard_hole_fits.hs:30:25)
+          (bound at hard_hole_fits.hs:29:25)
         xes :: Language.Haskell.Syntax.Extension.XExplicitSum GhcPs
-          (bound at hard_hole_fits.hs:30:21)
+          (bound at hard_hole_fits.hs:29:21)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         n :: Language.Haskell.Syntax.Basic.ConTag
-          (bound at hard_hole_fits.hs:30:25)
+          (bound at hard_hole_fits.hs:29:25)
         i :: Language.Haskell.Syntax.Basic.SumWidth
-          (bound at hard_hole_fits.hs:30:27)
+          (bound at hard_hole_fits.hs:29:27)
         maxBound :: forall a. Bounded a => a
           with maxBound @Int
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
@@ -344,15 +324,15 @@ hard_hole_fits.hs:30:35: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:31:28: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:30:28: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsCase xc gl mg) = _
     • Relevant bindings include
         mg :: MatchGroup GhcPs (LHsExpr GhcPs)
-          (bound at hard_hole_fits.hs:31:22)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:31:19)
+          (bound at hard_hole_fits.hs:30:22)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:30:19)
         xc :: Language.Haskell.Syntax.Extension.XCase GhcPs
-          (bound at hard_hole_fits.hs:31:16)
+          (bound at hard_hole_fits.hs:30:16)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -364,15 +344,15 @@ hard_hole_fits.hs:31:28: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:32:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:31:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsIf xi m_se gl gl') = _
     • Relevant bindings include
-        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:32:25)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:32:22)
-        m_se :: LHsExpr GhcPs (bound at hard_hole_fits.hs:32:17)
+        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:31:25)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:31:22)
+        m_se :: LHsExpr GhcPs (bound at hard_hole_fits.hs:31:17)
         xi :: Language.Haskell.Syntax.Extension.XIf GhcPs
-          (bound at hard_hole_fits.hs:32:14)
+          (bound at hard_hole_fits.hs:31:14)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -384,14 +364,14 @@ hard_hole_fits.hs:32:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:33:30: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:32:30: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsMultiIf xmi gls) = _
     • Relevant bindings include
         gls :: [LGRHS GhcPs (LHsExpr GhcPs)]
-          (bound at hard_hole_fits.hs:33:23)
+          (bound at hard_hole_fits.hs:32:23)
         xmi :: Language.Haskell.Syntax.Extension.XMultiIf GhcPs
-          (bound at hard_hole_fits.hs:33:19)
+          (bound at hard_hole_fits.hs:32:19)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -403,20 +383,20 @@ hard_hole_fits.hs:33:30: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:34:39: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:33:39: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’:
           testMe (HsLet xl tkLet gl tkIn gl') = _
     • Relevant bindings include
-        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:34:32)
+        gl' :: LHsExpr GhcPs (bound at hard_hole_fits.hs:33:32)
         tkIn :: Language.Haskell.Syntax.Concrete.LHsToken "in" GhcPs
-          (bound at hard_hole_fits.hs:34:27)
+          (bound at hard_hole_fits.hs:33:27)
         gl :: Language.Haskell.Syntax.Binds.HsLocalBinds GhcPs
-          (bound at hard_hole_fits.hs:34:24)
+          (bound at hard_hole_fits.hs:33:24)
         tkLet :: Language.Haskell.Syntax.Concrete.LHsToken "let" GhcPs
-          (bound at hard_hole_fits.hs:34:18)
+          (bound at hard_hole_fits.hs:33:18)
         xl :: Language.Haskell.Syntax.Extension.XLet GhcPs
-          (bound at hard_hole_fits.hs:34:15)
+          (bound at hard_hole_fits.hs:33:15)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -428,16 +408,16 @@ hard_hole_fits.hs:34:39: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:35:27: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:34:27: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsDo xd hsc gl) = _
     • Relevant bindings include
         gl :: Language.Haskell.Syntax.Extension.XRec
                 GhcPs [ExprLStmt GhcPs]
-          (bound at hard_hole_fits.hs:35:21)
-        hsc :: HsDoFlavour (bound at hard_hole_fits.hs:35:17)
+          (bound at hard_hole_fits.hs:34:21)
+        hsc :: HsDoFlavour (bound at hard_hole_fits.hs:34:17)
         xd :: Language.Haskell.Syntax.Extension.XDo GhcPs
-          (bound at hard_hole_fits.hs:35:14)
+          (bound at hard_hole_fits.hs:34:14)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -449,13 +429,13 @@ hard_hole_fits.hs:35:27: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:36:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:35:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (ExplicitList xel m_se) = _
     • Relevant bindings include
-        m_se :: [LHsExpr GhcPs] (bound at hard_hole_fits.hs:36:26)
+        m_se :: [LHsExpr GhcPs] (bound at hard_hole_fits.hs:35:26)
         xel :: Language.Haskell.Syntax.Extension.XExplicitList GhcPs
-          (bound at hard_hole_fits.hs:36:22)
+          (bound at hard_hole_fits.hs:35:22)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -467,16 +447,16 @@ hard_hole_fits.hs:36:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:37:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:36:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (RecordCon xrc gl hrf) = _
     • Relevant bindings include
-        hrf :: HsRecordBinds GhcPs (bound at hard_hole_fits.hs:37:26)
+        hrf :: HsRecordBinds GhcPs (bound at hard_hole_fits.hs:36:26)
         gl :: Language.Haskell.Syntax.Extension.XRec
                 GhcPs (Language.Haskell.Syntax.Pat.ConLikeP GhcPs)
-          (bound at hard_hole_fits.hs:37:23)
+          (bound at hard_hole_fits.hs:36:23)
         xrc :: Language.Haskell.Syntax.Extension.XRecordCon GhcPs
-          (bound at hard_hole_fits.hs:37:19)
+          (bound at hard_hole_fits.hs:36:19)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -488,14 +468,14 @@ hard_hole_fits.hs:37:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:38:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:37:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (RecordUpd xru gl gls) = _
     • Relevant bindings include
-        gls :: LHsRecUpdFields GhcPs (bound at hard_hole_fits.hs:38:26)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:38:23)
+        gls :: LHsRecUpdFields GhcPs (bound at hard_hole_fits.hs:37:26)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:37:23)
         xru :: Language.Haskell.Syntax.Extension.XRecordUpd GhcPs
-          (bound at hard_hole_fits.hs:38:19)
+          (bound at hard_hole_fits.hs:37:19)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -507,17 +487,17 @@ hard_hole_fits.hs:38:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:39:40: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:38:40: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’:
           testMe (ExprWithTySig xewts gl hwcb) = _
     • Relevant bindings include
         hwcb :: Language.Haskell.Syntax.Type.LHsSigWcType
                   (Language.Haskell.Syntax.Extension.NoGhcTc GhcPs)
-          (bound at hard_hole_fits.hs:39:32)
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:39:29)
+          (bound at hard_hole_fits.hs:38:32)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:38:29)
         xewts :: Language.Haskell.Syntax.Extension.XExprWithTySig GhcPs
-          (bound at hard_hole_fits.hs:39:23)
+          (bound at hard_hole_fits.hs:38:23)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -529,14 +509,14 @@ hard_hole_fits.hs:39:40: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:40:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:39:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (ArithSeq xas m_se asi) = _
     • Relevant bindings include
-        asi :: ArithSeqInfo GhcPs (bound at hard_hole_fits.hs:40:27)
-        m_se :: Maybe (SyntaxExpr GhcPs) (bound at hard_hole_fits.hs:40:22)
+        asi :: ArithSeqInfo GhcPs (bound at hard_hole_fits.hs:39:27)
+        m_se :: Maybe (SyntaxExpr GhcPs) (bound at hard_hole_fits.hs:39:22)
         xas :: Language.Haskell.Syntax.Extension.XArithSeq GhcPs
-          (bound at hard_hole_fits.hs:40:18)
+          (bound at hard_hole_fits.hs:39:18)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -548,13 +528,13 @@ hard_hole_fits.hs:40:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:41:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:40:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsTypedBracket xb hb) = _
     • Relevant bindings include
-        hb :: LHsExpr GhcPs (bound at hard_hole_fits.hs:41:27)
+        hb :: LHsExpr GhcPs (bound at hard_hole_fits.hs:40:27)
         xb :: Language.Haskell.Syntax.Extension.XTypedBracket GhcPs
-          (bound at hard_hole_fits.hs:41:24)
+          (bound at hard_hole_fits.hs:40:24)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -566,13 +546,13 @@ hard_hole_fits.hs:41:33: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:42:35: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:41:35: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsUntypedBracket xb hb) = _
     • Relevant bindings include
-        hb :: HsQuote GhcPs (bound at hard_hole_fits.hs:42:29)
+        hb :: HsQuote GhcPs (bound at hard_hole_fits.hs:41:29)
         xb :: Language.Haskell.Syntax.Extension.XUntypedBracket GhcPs
-          (bound at hard_hole_fits.hs:42:26)
+          (bound at hard_hole_fits.hs:41:26)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -584,13 +564,13 @@ hard_hole_fits.hs:42:35: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:43:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:42:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsTypedSplice xs hs) = _
     • Relevant bindings include
-        hs :: LHsExpr GhcPs (bound at hard_hole_fits.hs:43:26)
+        hs :: LHsExpr GhcPs (bound at hard_hole_fits.hs:42:26)
         xs :: Language.Haskell.Syntax.Extension.XTypedSplice GhcPs
-          (bound at hard_hole_fits.hs:43:23)
+          (bound at hard_hole_fits.hs:42:23)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -602,13 +582,13 @@ hard_hole_fits.hs:43:32: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:44:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:43:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsUntypedSplice xs hs) = _
     • Relevant bindings include
-        hs :: HsUntypedSplice GhcPs (bound at hard_hole_fits.hs:44:28)
+        hs :: HsUntypedSplice GhcPs (bound at hard_hole_fits.hs:43:28)
         xs :: Language.Haskell.Syntax.Extension.XUntypedSplice GhcPs
-          (bound at hard_hole_fits.hs:44:25)
+          (bound at hard_hole_fits.hs:43:25)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -620,15 +600,15 @@ hard_hole_fits.hs:44:34: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:45:29: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:44:29: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsProc xp pat gl) = _
     • Relevant bindings include
-        gl :: LHsCmdTop GhcPs (bound at hard_hole_fits.hs:45:23)
+        gl :: LHsCmdTop GhcPs (bound at hard_hole_fits.hs:44:23)
         pat :: Language.Haskell.Syntax.Pat.LPat GhcPs
-          (bound at hard_hole_fits.hs:45:19)
+          (bound at hard_hole_fits.hs:44:19)
         xp :: Language.Haskell.Syntax.Extension.XProc GhcPs
-          (bound at hard_hole_fits.hs:45:16)
+          (bound at hard_hole_fits.hs:44:16)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -640,13 +620,13 @@ hard_hole_fits.hs:45:29: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:46:27: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:45:27: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (HsStatic xs gl) = _
     • Relevant bindings include
-        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:46:21)
+        gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:45:21)
         xs :: Language.Haskell.Syntax.Extension.XStatic GhcPs
-          (bound at hard_hole_fits.hs:46:18)
+          (bound at hard_hole_fits.hs:45:18)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a
@@ -658,16 +638,16 @@ hard_hole_fits.hs:46:27: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           (imported from ‘Prelude’ at hard_hole_fits.hs:8:8-20
            (and originally defined in ‘GHC.Enum’))
 
-hard_hole_fits.hs:47:1: warning: [GHC-53633] [-Woverlapping-patterns (in -Wdefault)]
+hard_hole_fits.hs:46:1: warning: [GHC-53633] [-Woverlapping-patterns (in -Wdefault)]
     Pattern match is redundant
     In an equation for ‘testMe’: testMe (XExpr xe) = ...
 
-hard_hole_fits.hs:47:21: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+hard_hole_fits.hs:46:21: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
     • Found hole: _ :: Int
     • In an equation for ‘testMe’: testMe (XExpr xe) = _
     • Relevant bindings include
         xe :: Language.Haskell.Syntax.Extension.XXExpr GhcPs
-          (bound at hard_hole_fits.hs:47:15)
+          (bound at hard_hole_fits.hs:46:15)
         testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
       Valid hole fits include
         maxBound :: forall a. Bounded a => a



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

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


More information about the ghc-commits mailing list