summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAndreas Klebinger <klebinger.andreas@gmx.at>2021-11-12 15:45:18 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-11-23 01:07:29 -0500
commit680ef2c8eafa102d8ed5866d5ccf2872f5d0f269 (patch)
tree3929d4f6d120b779b9e0cbb2551a37091948c38e
parent68a3665a73c2a41820587be5a79674321d0793a0 (diff)
downloadhaskell-680ef2c8eafa102d8ed5866d5ccf2872f5d0f269.tar.gz
CmmSink: Be more aggressive in removing no-op assignments.
No-op assignments like R1 = R1 are not only wasteful. They can also inhibit other optimizations like inlining assignments that read from R1. We now check for assignments being a no-op before and after we simplify the RHS in Cmm sink which should eliminate most of these no-ops.
-rw-r--r--compiler/GHC/Cmm/Sink.hs60
-rw-r--r--testsuite/driver/testlib.py23
-rw-r--r--testsuite/tests/cmm/should_compile/all.T2
-rw-r--r--testsuite/tests/cmm/should_compile/cmm_sink_sp.cmm24
-rw-r--r--testsuite/tests/cmm/should_compile/cmm_sink_sp.stderr42
-rw-r--r--testsuite/tests/typecheck/should_compile/T16875.hs13
-rw-r--r--testsuite/tests/typecheck/should_compile/T16875.stderr12
-rw-r--r--testsuite/tests/typecheck/should_compile/hard_hole_fits.hs48
-rw-r--r--testsuite/tests/typecheck/should_compile/hard_hole_fits.stderr679
9 files changed, 897 insertions, 6 deletions
diff --git a/compiler/GHC/Cmm/Sink.hs b/compiler/GHC/Cmm/Sink.hs
index 3ef58b3648..19160065ba 100644
--- a/compiler/GHC/Cmm/Sink.hs
+++ b/compiler/GHC/Cmm/Sink.hs
@@ -318,20 +318,64 @@ walk platform nodes assigs = go nodes emptyBlock assigs
where
go [] block as = (block, as)
go ((live,node):ns) block as
+ -- discard nodes representing dead assignment
| shouldDiscard node live = go ns block as
- -- discard dead assignment
+ -- sometimes only after simplification we can tell we can discard the node.
+ -- See Note [Discard simplified nodes]
+ | noOpAssignment node2 = go ns block as
+ -- Pick up interesting assignments
| Just a <- shouldSink platform node2 = go ns block (a : as1)
+ -- Try inlining, drop assignments and move on
| otherwise = go ns block' as'
where
+ -- Simplify node
node1 = constantFoldNode platform node
+ -- Inline assignments
(node2, as1) = tryToInline platform live node1 as
+ -- Drop any earlier assignments conflicting with node2
(dropped, as') = dropAssignmentsSimple platform
(\a -> conflicts platform a node2) as1
+ -- Walk over the rest of the block. Includes dropped assignments
block' = foldl' blockSnoc block dropped `blockSnoc` node2
+{- Note [Discard simplified nodes]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider a sequence like this:
+
+ _c1::P64 = R1;
+ _c3::I64 = I64[_c1::P64 + 1];
+ R1 = _c1::P64;
+ P64[Sp - 72] = _c1::P64;
+ I64[Sp - 64] = _c3::I64;
+
+If we discard assignments *before* simplifying nodes when we get to `R1 = _c1`.
+This is then simplified into `R1 = `R1` and as a consequence prevents sinking of
+loads from R1. What happens is that we:
+ * Check if we can discard the node `R1 = _c1 (no)
+ * Simplify the node to R1 = R1
+ * We check all remaining assignments for conflicts.
+ * The assignment `_c3 = [R1 + 1]`; (R1 already inlined on pickup)
+ conflicts with R1 = R1, because it reads `R1` and the node writes
+ to R1
+ * This is clearly no-sensical because `R1 = R1` doesn't affect R1's value.
+
+The solutions is to check if we can discard nodes before and *after* simplifying
+them. We could only do it after as well, but I assume doing it early might save
+some work.
+
+That is if we process a assignment node we now:
+ * Check if it can be discarded (because it's dead or a no-op)
+ * Simplify the rhs of the assignment.
+ * New: Check again if it might be a no-op now.
+ * ...
+
+This can help with problems like the one reported in #20334. For a full example see the test
+cmm_sink_sp.
+
+-}
--
-- Heuristic to decide whether to pick up and sink an assignment
@@ -358,10 +402,19 @@ shouldSink _ _other = Nothing
shouldDiscard :: CmmNode e x -> LRegSet -> Bool
shouldDiscard node live
= case node of
+ -- r = r
CmmAssign r (CmmReg r') | r == r' -> True
+ -- r = e, r is dead after assignment
CmmAssign (CmmLocal r) _ -> not (r `elemLRegSet` live)
_otherwise -> False
+noOpAssignment :: CmmNode e x -> Bool
+noOpAssignment node
+ = case node of
+ -- r = r
+ CmmAssign r (CmmReg r') | r == r' -> True
+ _otherwise -> False
+
toNode :: Assignment -> CmmNode O O
toNode (r,rhs,_) = CmmAssign (CmmLocal r) rhs
@@ -379,7 +432,9 @@ dropAssignments platform should_drop state assigs
go _ [] dropped kept = (dropped, kept)
go state (assig : rest) dropped kept
- | conflict = go state' rest (toNode assig : dropped) kept
+ | conflict =
+ let !node = toNode assig
+ in go state' rest (node : dropped) kept
| otherwise = go state' rest dropped (assig:kept)
where
(dropit, state') = should_drop assig state
@@ -394,7 +449,6 @@ dropAssignments platform should_drop state assigs
tryToInline
:: forall x. Platform
-> LRegSet -- set of registers live after this
- -- -> LocalRegSet -- set of registers live after this
-- node. We cannot inline anything
-- that is live after the node, unless
-- it is small enough to duplicate.
diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py
index efeaa94b89..d4c8fc38f7 100644
--- a/testsuite/driver/testlib.py
+++ b/testsuite/driver/testlib.py
@@ -800,9 +800,26 @@ def check_errmsg(needle):
return "%s not contained in -ddump-simpl\n" % needle
return normalise_errmsg_fun(norm)
-def grep_errmsg(needle):
- def norm(str):
- return "".join(filter(lambda l: re.search(needle, l), str.splitlines(True)))
+# grep_errmsg(regex,[match_only])
+# If match_only = True we only check the part of the error
+# that matches the regex.
+def grep_errmsg(needle:str, match_only = False):
+
+ def get_match(str:str):
+ m = re.search(needle,str)
+ if m:
+ return m.group(0)
+ else:
+ return None
+
+ def norm(str) -> str:
+ if not match_only:
+ return "".join( filter(lambda l: re.search(needle,l),
+ str.splitlines(True)))
+ else:
+ matches = [get_match(x) for x in str.splitlines(True)]
+ res = "\n".join([x for x in matches if x])
+ return res
return normalise_errmsg_fun(norm)
def multiline_grep_errmsg(needle):
diff --git a/testsuite/tests/cmm/should_compile/all.T b/testsuite/tests/cmm/should_compile/all.T
index 5ae7c51726..735bd1c9fd 100644
--- a/testsuite/tests/cmm/should_compile/all.T
+++ b/testsuite/tests/cmm/should_compile/all.T
@@ -1,4 +1,6 @@
#
test('selfloop', [cmm_src], compile, ['-no-hs-main'])
+test('cmm_sink_sp', [ only_ways(['optasm']), grep_errmsg('I64\[Sp.*\].*=.*\[.*R1.*\].*;',True), cmm_src], compile, ['-no-hs-main -ddump-cmm -dsuppress-uniques -O'])
+
test('T16930', normal, makefile_test, ['T16930'])
test('T17442', normal, compile, [''])
diff --git a/testsuite/tests/cmm/should_compile/cmm_sink_sp.cmm b/testsuite/tests/cmm/should_compile/cmm_sink_sp.cmm
new file mode 100644
index 0000000000..1b2d02dd6f
--- /dev/null
+++ b/testsuite/tests/cmm/should_compile/cmm_sink_sp.cmm
@@ -0,0 +1,24 @@
+#include "Cmm.h"
+
+stg_sink_things ( P_ x1 )
+{
+ W_ res;
+ W_ x2, x3, x4, x5, x6, x7, x8, x9;
+
+ // Should produce a series of loads that are sunk into
+ // stores to Sp like this:
+ // I64[Sp - 64] = I64[R1 + 1]; // CmmStore
+ // I64[Sp - 56] = I64[R1 + 2]; // CmmStore
+ x2 = W_[x1+1];
+ x3 = W_[x1+2];
+ x4 = W_[x1+3];
+ x5 = W_[x1+4];
+ x6 = W_[x1+5];
+ x7 = W_[x1+6];
+ x8 = W_[x1+7];
+ x9 = W_[x1+8];
+
+ call R1(x1);
+ res = x1 + x2 + x3 + x4 + x5 + x6 + x7 + x8 + x9;
+ return (res);
+} \ No newline at end of file
diff --git a/testsuite/tests/cmm/should_compile/cmm_sink_sp.stderr b/testsuite/tests/cmm/should_compile/cmm_sink_sp.stderr
new file mode 100644
index 0000000000..ca5f89ea5b
--- /dev/null
+++ b/testsuite/tests/cmm/should_compile/cmm_sink_sp.stderr
@@ -0,0 +1,42 @@
+
+==================== Output Cmm ====================
+[stg_sink_things() { // [R1]
+ { info_tbls: [(cb,
+ label: block_info
+ rep: StackRep [False, True, True, True, True, True, True, True,
+ True]
+ srt: Nothing)]
+ stack_info: arg_space: 8
+ }
+ {offset
+ _lbl_: // global
+ //tick src<cmm_sink_sp.cmm:(4,1)-(24,1)>
+ //tick src<cmm_sink_sp.cmm:12:8-22>
+ //tick src<cmm_sink_sp.cmm:13:8-22>
+ //tick src<cmm_sink_sp.cmm:14:8-22>
+ //tick src<cmm_sink_sp.cmm:15:8-22>
+ //tick src<cmm_sink_sp.cmm:16:8-22>
+ //tick src<cmm_sink_sp.cmm:17:8-22>
+ //tick src<cmm_sink_sp.cmm:18:8-22>
+ //tick src<cmm_sink_sp.cmm:19:8-22>
+ I64[Sp - 80] = cb; // CmmStore
+ P64[Sp - 72] = R1; // CmmStore
+ I64[Sp - 64] = I64[R1 + 1]; // CmmStore
+ I64[Sp - 56] = I64[R1 + 2]; // CmmStore
+ I64[Sp - 48] = I64[R1 + 3]; // CmmStore
+ I64[Sp - 40] = I64[R1 + 4]; // CmmStore
+ I64[Sp - 32] = I64[R1 + 5]; // CmmStore
+ I64[Sp - 24] = I64[R1 + 6]; // CmmStore
+ I64[Sp - 16] = I64[R1 + 7]; // CmmStore
+ I64[Sp - 8] = I64[R1 + 8]; // CmmStore
+ Sp = Sp - 80; // CmmAssign
+ call (R1)(R1) returns to cb, args: 8, res: 8, upd: 8; // CmmCall
+ _lbl_: // global
+ //tick src<cmm_sink_sp.cmm:22:9-53>
+ R1 = P64[Sp + 8] + (I64[Sp + 16] + (I64[Sp + 24] + (I64[Sp + 32] + (I64[Sp + 40] + (I64[Sp + 48] + (I64[Sp + 56] + (I64[Sp + 64] + I64[Sp + 72]))))))); // CmmAssign
+ Sp = Sp + 80; // CmmAssign
+ call (P64[Sp])(R1) args: 8, res: 0, upd: 8; // CmmCall
+ }
+ }]
+
+
diff --git a/testsuite/tests/typecheck/should_compile/T16875.hs b/testsuite/tests/typecheck/should_compile/T16875.hs
new file mode 100644
index 0000000000..0ba3c17d5b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T16875.hs
@@ -0,0 +1,13 @@
+module T16875 where
+
+import Control.Applicative
+import Control.Monad
+import Data.Kind
+import Data.List
+import Data.Maybe
+import Data.String
+import GHC.Exts
+import GHC.Types
+
+a = _
+
diff --git a/testsuite/tests/typecheck/should_compile/T16875.stderr b/testsuite/tests/typecheck/should_compile/T16875.stderr
new file mode 100644
index 0000000000..af6954792e
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T16875.stderr
@@ -0,0 +1,12 @@
+
+T16875.hs:12:5: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: p
+ Where: ‘p’ is a rigid type variable bound by
+ the inferred type of a :: p
+ at T16875.hs:12:1-5
+ • In an equation for ‘a’: a = _
+ • Relevant bindings include a :: p (bound at T16875.hs:12:1)
+ Valid hole fits include
+ a :: forall {p}. p
+ with a
+ (defined at T16875.hs:12:1)
diff --git a/testsuite/tests/typecheck/should_compile/hard_hole_fits.hs b/testsuite/tests/typecheck/should_compile/hard_hole_fits.hs
new file mode 100644
index 0000000000..a1cbec4b59
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/hard_hole_fits.hs
@@ -0,0 +1,48 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
+
+-- typechecking goes really fast if you uncomment this line
+
+-- {-# OPTIONS_GHC -fmax-valid-hole-fits=0 #-}
+
+module SlowTypecheck where
+
+import Language.Haskell.Syntax.Expr
+import GHC (GhcPs)
+
+testMe :: HsExpr GhcPs -> Int
+testMe (HsVar a b) = _
+testMe (HsUnboundVar xuv uv) = _
+testMe (HsOverLabel xol m_ip) = _
+testMe (HsIPVar xv hin) = _
+testMe (HsOverLit xole hol) = _
+testMe (HsLit xle hl) = _
+testMe (HsLam xl mg) = _
+testMe (HsLamCase xlc mg) = _
+testMe (HsApp xa gl gl') = _
+testMe (HsAppType xate gl hwcb) = _
+testMe (OpApp xoa gl gl' gl2) = _
+testMe (NegApp xna gl se) = _
+testMe (HsPar xp gl ab ac) = _
+testMe (SectionL xsl gl gl') = _
+testMe (SectionR xsr gl gl') = _
+testMe (ExplicitTuple xet gls box) = _
+testMe (ExplicitSum xes n i gl) = _
+testMe (HsCase xc gl mg) = _
+testMe (HsIf xi m_se gl gl' ) = _
+testMe (HsMultiIf xmi gls) = _
+testMe (HsLet xl tkLet gl tkIn gl') = _
+testMe (HsDo xd hsc gl) = _
+testMe (ExplicitList xel m_se) = _
+testMe (RecordCon xrc gl hrf) = _
+testMe (RecordUpd xru gl gls) = _
+testMe (ExprWithTySig xewts gl hwcb) = _
+testMe (ArithSeq xas m_se asi) = _
+testMe (HsBracket xb hb) = _
+testMe (HsRnBracketOut xrbo hb prss) = _
+testMe (HsTcBracketOut xtbo hb ptss as) = _
+testMe (HsSpliceE xse hs) = _
+testMe (HsProc xp pat gl) = _
+testMe (HsStatic xs gl) = _
+testMe (XExpr xe) = _
+
diff --git a/testsuite/tests/typecheck/should_compile/hard_hole_fits.stderr b/testsuite/tests/typecheck/should_compile/hard_hole_fits.stderr
new file mode 100644
index 0000000000..78a3584f1c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/hard_hole_fits.stderr
@@ -0,0 +1,679 @@
+
+hard_hole_fits.hs:14:22: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsVar a b) = _
+ • Relevant bindings include
+ b :: Language.Haskell.Syntax.Extension.LIdP GhcPs
+ (bound at hard_hole_fits.hs:14:17)
+ a :: Language.Haskell.Syntax.Extension.XVar GhcPs
+ (bound at hard_hole_fits.hs:14:15)
+ 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:15:32: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsUnboundVar xuv uv) = _
+ • Relevant bindings include
+ uv :: GHC.Types.Name.Occurrence.OccName
+ (bound at hard_hole_fits.hs:15:26)
+ xuv :: Language.Haskell.Syntax.Extension.XUnboundVar GhcPs
+ (bound at hard_hole_fits.hs:15:22)
+ 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:16:33: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsOverLabel xol m_ip) = _
+ • Relevant bindings include
+ m_ip :: GHC.Data.FastString.FastString
+ (bound at hard_hole_fits.hs:16:25)
+ xol :: Language.Haskell.Syntax.Extension.XOverLabel GhcPs
+ (bound at hard_hole_fits.hs:16:21)
+ 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:17:27: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsIPVar xv hin) = _
+ • Relevant bindings include
+ hin :: Language.Haskell.Syntax.Type.HsIPName
+ (bound at hard_hole_fits.hs:17:20)
+ xv :: Language.Haskell.Syntax.Extension.XIPVar GhcPs
+ (bound at hard_hole_fits.hs:17:17)
+ 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:18:31: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsOverLit xole hol) = _
+ • Relevant bindings include
+ hol :: Language.Haskell.Syntax.Lit.HsOverLit GhcPs
+ (bound at hard_hole_fits.hs:18:24)
+ xole :: Language.Haskell.Syntax.Extension.XOverLitE GhcPs
+ (bound at hard_hole_fits.hs:18: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:19:25: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsLit xle hl) = _
+ • Relevant bindings include
+ hl :: Language.Haskell.Syntax.Lit.HsLit GhcPs
+ (bound at hard_hole_fits.hs:19:19)
+ xle :: Language.Haskell.Syntax.Extension.XLitE GhcPs
+ (bound at hard_hole_fits.hs:19:15)
+ 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:20:24: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsLam xl 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:15)
+ 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:21:29: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsLamCase xlc mg) = _
+ • Relevant bindings include
+ mg :: MatchGroup GhcPs (LHsExpr GhcPs)
+ (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: [-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)
+ xa :: Language.Haskell.Syntax.Extension.XApp GhcPs
+ (bound at hard_hole_fits.hs:22:15)
+ 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:23:35: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsAppType xate gl hwcb) = _
+ • Relevant bindings include
+ hwcb :: Language.Haskell.Syntax.Type.LHsWcType
+ (Language.Haskell.Syntax.Extension.NoGhcTc GhcPs)
+ (bound at hard_hole_fits.hs:23:27)
+ gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:23:24)
+ xate :: Language.Haskell.Syntax.Extension.XAppTypeE GhcPs
+ (bound at hard_hole_fits.hs:23: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:24:33: warning: [-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)
+ xoa :: Language.Haskell.Syntax.Extension.XOpApp GhcPs
+ (bound at hard_hole_fits.hs:24:15)
+ 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:25:29: warning: [-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)
+ xna :: Language.Haskell.Syntax.Extension.XNegApp GhcPs
+ (bound at hard_hole_fits.hs:25:16)
+ 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:26:30: warning: [-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.Extension.LHsToken ")" GhcPs
+ (bound at hard_hole_fits.hs:26:24)
+ ab :: LHsExpr GhcPs (bound at hard_hole_fits.hs:26:21)
+ gl :: Language.Haskell.Syntax.Extension.LHsToken "(" GhcPs
+ (bound at hard_hole_fits.hs:26:18)
+ xp :: Language.Haskell.Syntax.Extension.XPar GhcPs
+ (bound at hard_hole_fits.hs:26:15)
+ 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:27:32: warning: [-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)
+ xsl :: Language.Haskell.Syntax.Extension.XSectionL GhcPs
+ (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
+ 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:28:32: warning: [-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)
+ xsr :: Language.Haskell.Syntax.Extension.XSectionR GhcPs
+ (bound at hard_hole_fits.hs:28:18)
+ 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:29:38: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’:
+ testMe (ExplicitTuple xet gls box) = _
+ • Relevant bindings include
+ box :: GHC.Types.Basic.Boxity (bound at hard_hole_fits.hs:29:31)
+ gls :: [HsTupArg GhcPs] (bound at hard_hole_fits.hs:29:27)
+ xet :: Language.Haskell.Syntax.Extension.XExplicitTuple GhcPs
+ (bound at hard_hole_fits.hs:29:23)
+ 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:30:35: warning: [-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)
+ i :: GHC.Types.Basic.Arity (bound at hard_hole_fits.hs:30:27)
+ n :: GHC.Types.Basic.ConTag (bound at hard_hole_fits.hs:30:25)
+ xes :: Language.Haskell.Syntax.Extension.XExplicitSum GhcPs
+ (bound at hard_hole_fits.hs:30:21)
+ testMe :: HsExpr GhcPs -> Int (bound at hard_hole_fits.hs:14:1)
+ Valid hole fits include
+ n :: GHC.Types.Basic.ConTag (bound at hard_hole_fits.hs:30:25)
+ i :: GHC.Types.Basic.Arity (bound at hard_hole_fits.hs:30:27)
+ 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:31:28: warning: [-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)
+ xc :: Language.Haskell.Syntax.Extension.XCase GhcPs
+ (bound at hard_hole_fits.hs:31:16)
+ 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:32:33: warning: [-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)
+ xi :: Language.Haskell.Syntax.Extension.XIf GhcPs
+ (bound at hard_hole_fits.hs:32:14)
+ 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:33:30: warning: [-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)
+ xmi :: Language.Haskell.Syntax.Extension.XMultiIf GhcPs
+ (bound at hard_hole_fits.hs:33: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:34:39: warning: [-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)
+ tkIn :: Language.Haskell.Syntax.Extension.LHsToken "in" GhcPs
+ (bound at hard_hole_fits.hs:34:27)
+ gl :: Language.Haskell.Syntax.Binds.HsLocalBinds GhcPs
+ (bound at hard_hole_fits.hs:34:24)
+ tkLet :: Language.Haskell.Syntax.Extension.LHsToken "let" GhcPs
+ (bound at hard_hole_fits.hs:34:18)
+ xl :: Language.Haskell.Syntax.Extension.XLet GhcPs
+ (bound at hard_hole_fits.hs:34:15)
+ 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:35:27: warning: [-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)
+ xd :: Language.Haskell.Syntax.Extension.XDo GhcPs
+ (bound at hard_hole_fits.hs:35:14)
+ 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:36:34: warning: [-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)
+ xel :: Language.Haskell.Syntax.Extension.XExplicitList GhcPs
+ (bound at hard_hole_fits.hs:36:22)
+ 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:37:33: warning: [-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)
+ gl :: Language.Haskell.Syntax.Extension.XRec
+ GhcPs (Language.Haskell.Syntax.Pat.ConLikeP GhcPs)
+ (bound at hard_hole_fits.hs:37:23)
+ xrc :: Language.Haskell.Syntax.Extension.XRecordCon GhcPs
+ (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
+ 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:38:33: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (RecordUpd xru gl gls) = _
+ • Relevant bindings include
+ gls :: Either
+ [Language.Haskell.Syntax.Pat.LHsRecUpdField GhcPs]
+ [LHsRecUpdProj GhcPs]
+ (bound at hard_hole_fits.hs:38:26)
+ gl :: LHsExpr GhcPs (bound at hard_hole_fits.hs:38:23)
+ xru :: Language.Haskell.Syntax.Extension.XRecordUpd GhcPs
+ (bound at hard_hole_fits.hs:38: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:39:40: warning: [-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)
+ xewts :: Language.Haskell.Syntax.Extension.XExprWithTySig GhcPs
+ (bound at hard_hole_fits.hs:39:23)
+ 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:40:34: warning: [-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)
+ xas :: Language.Haskell.Syntax.Extension.XArithSeq GhcPs
+ (bound at hard_hole_fits.hs:40:18)
+ 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:41:28: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsBracket xb hb) = _
+ • Relevant bindings include
+ hb :: HsBracket GhcPs (bound at hard_hole_fits.hs:41:22)
+ xb :: Language.Haskell.Syntax.Extension.XBracket GhcPs
+ (bound at hard_hole_fits.hs:41: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:42:40: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’:
+ testMe (HsRnBracketOut xrbo hb prss) = _
+ • Relevant bindings include
+ prss :: [PendingRnSplice' GhcPs] (bound at hard_hole_fits.hs:42:32)
+ hb :: HsBracket (HsBracketRn GhcPs)
+ (bound at hard_hole_fits.hs:42:29)
+ xrbo :: Language.Haskell.Syntax.Extension.XRnBracketOut GhcPs
+ (bound at hard_hole_fits.hs:42:24)
+ 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:43:43: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’:
+ testMe (HsTcBracketOut xtbo hb ptss as) = _
+ • Relevant bindings include
+ as :: [PendingTcSplice' GhcPs] (bound at hard_hole_fits.hs:43:37)
+ ptss :: HsBracket (HsBracketRn GhcPs)
+ (bound at hard_hole_fits.hs:43:32)
+ hb :: Maybe GHC.Tc.Types.Evidence.QuoteWrapper
+ (bound at hard_hole_fits.hs:43:29)
+ xtbo :: Language.Haskell.Syntax.Extension.XTcBracketOut GhcPs
+ (bound at hard_hole_fits.hs:43:24)
+ 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:44:29: warning: [-Wtyped-holes (in -Wdefault)]
+ • Found hole: _ :: Int
+ • In an equation for ‘testMe’: testMe (HsSpliceE xse hs) = _
+ • Relevant bindings include
+ hs :: HsSplice GhcPs (bound at hard_hole_fits.hs:44:23)
+ xse :: Language.Haskell.Syntax.Extension.XSpliceE GhcPs
+ (bound at hard_hole_fits.hs:44: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:45:29: warning: [-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)
+ pat :: Language.Haskell.Syntax.Pat.LPat GhcPs
+ (bound at hard_hole_fits.hs:45:19)
+ xp :: Language.Haskell.Syntax.Extension.XProc GhcPs
+ (bound at hard_hole_fits.hs:45:16)
+ 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:46:27: warning: [-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)
+ xs :: Language.Haskell.Syntax.Extension.XStatic GhcPs
+ (bound at hard_hole_fits.hs:46:18)
+ 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:47:1: warning: [-Woverlapping-patterns (in -Wdefault)]
+ Pattern match is redundant
+ In an equation for ‘testMe’: testMe (XExpr xe) = ...
+
+hard_hole_fits.hs:47:21: warning: [-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)
+ 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’))