summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
authorSebastian Graf <sebastian.graf@kit.edu>2020-04-14 13:58:25 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-05-01 10:38:16 -0400
commitfd7ea0fee92a60f9658254cc4fe3abdb4ff299b1 (patch)
tree5fceecf0ca4885f1dcfa64b437eb20851a975b77 /testsuite
parent8b51fcbd67ca17a6dcc2f9e5a29176f836bf11d2 (diff)
downloadhaskell-fd7ea0fee92a60f9658254cc4fe3abdb4ff299b1.tar.gz
PmCheck: Pick up `EvVar`s bound in `HsWrapper`s for long-distance info
`HsWrapper`s introduce evidence bindings through `WpEvLam` which the pattern-match coverage checker should be made aware of. Failing to do so caused #18049, where the resulting impreciseness of imcompleteness warnings seemingly contradicted with `-Winaccessible-code`. The solution is simple: Collect all the evidence binders of an `HsWrapper` and add it to the ambient `Deltas` before desugaring the wrapped expression. But that means we pick up many more evidence bindings, even when they wrap around code without a single pattern match to check! That regressed `T3064` by over 300%, so now we are adding long-distance info lazily through judicious use of `unsafeInterleaveIO`. Fixes #18049.
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/pmcheck/should_compile/T18049.hs29
-rw-r--r--testsuite/tests/pmcheck/should_compile/all.T2
2 files changed, 31 insertions, 0 deletions
diff --git a/testsuite/tests/pmcheck/should_compile/T18049.hs b/testsuite/tests/pmcheck/should_compile/T18049.hs
new file mode 100644
index 0000000000..b63ffdf751
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T18049.hs
@@ -0,0 +1,29 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE RankNTypes #-}
+{-# OPTIONS_GHC -Wincomplete-patterns -fforce-recomp #-}
+module Bug where
+
+import Data.Kind
+
+data SBool :: Bool -> Type where
+ SFalse :: SBool False
+ STrue :: SBool True
+
+f :: SBool b
+ -> (b ~ True => SBool b -> r)
+ -> (b ~ False => SBool b -> r)
+ -> r
+f x t f =
+ case x of
+ SFalse -> f x
+ STrue -> t x
+
+g :: forall b. SBool b -> ()
+g x = f x
+ (\x' ->
+ case x' of
+ -- SFalse -> ()
+ STrue -> ())
+ (\_ -> ())
diff --git a/testsuite/tests/pmcheck/should_compile/all.T b/testsuite/tests/pmcheck/should_compile/all.T
index 0c3bfcf510..2e4e3942ac 100644
--- a/testsuite/tests/pmcheck/should_compile/all.T
+++ b/testsuite/tests/pmcheck/should_compile/all.T
@@ -118,6 +118,8 @@ test('T17977', collect_compiler_stats('bytes allocated',10), compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
test('T17977b', collect_compiler_stats('bytes allocated',10), compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
+test('T18049', normal, compile,
+ ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
# Other tests
test('pmc001', [], compile,