[commit: ghc] master: Add regression test for #15321 (e835fdb)
git at git.haskell.org
git at git.haskell.org
Wed Jul 4 13:43:40 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/e835fdb18cca66820728afce9c924a1c71f17fee/ghc
>---------------------------------------------------------------
commit e835fdb18cca66820728afce9c924a1c71f17fee
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date: Wed Jul 4 16:43:13 2018 +0300
Add regression test for #15321
>---------------------------------------------------------------
e835fdb18cca66820728afce9c924a1c71f17fee
testsuite/tests/th/T15321.hs | 9 +++++++++
testsuite/tests/th/T15321.stderr | 12 ++++++++++++
testsuite/tests/th/all.T | 1 +
3 files changed, 22 insertions(+)
diff --git a/testsuite/tests/th/T15321.hs b/testsuite/tests/th/T15321.hs
new file mode 100644
index 0000000..0f0b4d5
--- /dev/null
+++ b/testsuite/tests/th/T15321.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T15321 where
+
+foo :: String
+foo = test
+
+bar :: String
+bar = $(_ "baz")
diff --git a/testsuite/tests/th/T15321.stderr b/testsuite/tests/th/T15321.stderr
new file mode 100644
index 0000000..7807bcf
--- /dev/null
+++ b/testsuite/tests/th/T15321.stderr
@@ -0,0 +1,12 @@
+
+T15321.hs:9:9: error:
+ • Found hole: _ :: [Char] -> Language.Haskell.TH.Lib.Internal.ExpQ
+ • In the expression: _
+ In the expression: _ "baz"
+ In the untyped splice: $(_ "baz")
+ • Valid hole fits include
+ fail :: forall (m :: * -> *) a. Monad m => String -> m a
+ with fail @Language.Haskell.TH.Syntax.Q
+ @Language.Haskell.TH.Syntax.Exp
+ (imported from ‘Prelude’ at T15321.hs:3:8-13
+ (and originally defined in ‘GHC.Base’))
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index f86cc96..f95e8f4 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -415,3 +415,4 @@ test('T14885a', normal, compile, [''])
test('T14885b', normal, compile, [''])
test('T14885c', normal, compile, [''])
test('T15243', normal, compile, ['-dsuppress-uniques'])
+test('T15321', normal, compile_fail, [''])
More information about the ghc-commits
mailing list