summaryrefslogtreecommitdiff
path: root/testsuite/tests
diff options
context:
space:
mode:
authorAlec Theriault <alec.theriault@gmail.com>2018-10-04 18:13:15 -0400
committerRyan Scott <ryan.gl.scott@gmail.com>2018-10-04 18:13:16 -0400
commitba163c3b3502df039e589c5bb0bc9ea767267b2a (patch)
treef33232f02ca1c775694153381e3b0d69771c89c4 /testsuite/tests
parentbace26aadaafa4064e78f9ed088c1e2217221acc (diff)
downloadhaskell-ba163c3b3502df039e589c5bb0bc9ea767267b2a.tar.gz
Don't drop arguments in TH type arguments
Summary: When converting from TH AST back to HsType, we were occasionally dropping type arguments. This resulted in incorrectly accepted programs as well as incorrectly rejected programs. Test Plan: make TEST=T15360a && make TEST=T15360b Reviewers: goldfire, bgamari, tdammers Reviewed By: bgamari, tdammers Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15360 Differential Revision: https://phabricator.haskell.org/D5188
Diffstat (limited to 'testsuite/tests')
-rw-r--r--testsuite/tests/th/T15360a.hs12
-rw-r--r--testsuite/tests/th/T15360b.hs20
-rw-r--r--testsuite/tests/th/T15360b.stderr20
-rw-r--r--testsuite/tests/th/all.T2
4 files changed, 54 insertions, 0 deletions
diff --git a/testsuite/tests/th/T15360a.hs b/testsuite/tests/th/T15360a.hs
new file mode 100644
index 0000000000..4839ccfcc1
--- /dev/null
+++ b/testsuite/tests/th/T15360a.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T15360a where
+
+import Language.Haskell.TH
+
+data T a b c = Mk a b c
+
+bar :: $( return $ AppT (InfixT (ConT ''Int) ''T (ConT ''Bool)) (ConT ''Double) )
+bar = Mk 5 True 3.14
+
+baz :: $( return $ AppT (ParensT (ConT ''Maybe)) (ConT ''Int) )
+baz = Just 5
diff --git a/testsuite/tests/th/T15360b.hs b/testsuite/tests/th/T15360b.hs
new file mode 100644
index 0000000000..276d2cd7c2
--- /dev/null
+++ b/testsuite/tests/th/T15360b.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE QuasiQuotes #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE StarIsType #-}
+module T15360b where
+
+import Data.Kind
+import Data.Proxy
+
+x :: Proxy $([t| * Double |])
+x = Proxy
+
+y :: Proxy $([t| 1 Int |])
+y = Proxy
+
+z :: Proxy $([t| Constraint Bool |])
+z = Proxy
+
+w :: Proxy $([t| '[] Int |])
+w = Proxy
diff --git a/testsuite/tests/th/T15360b.stderr b/testsuite/tests/th/T15360b.stderr
new file mode 100644
index 0000000000..8175c12556
--- /dev/null
+++ b/testsuite/tests/th/T15360b.stderr
@@ -0,0 +1,20 @@
+
+T15360b.hs:10:14: error:
+ • Expected kind ‘* -> k4’, but ‘Type’ has kind ‘*’
+ • In the first argument of ‘Proxy’, namely ‘(Type Double)’
+ In the type signature: x :: Proxy (Type Double)
+
+T15360b.hs:13:14: error:
+ • Expected kind ‘* -> k3’, but ‘1’ has kind ‘GHC.Types.Nat’
+ • In the first argument of ‘Proxy’, namely ‘(1 Int)’
+ In the type signature: y :: Proxy (1 Int)
+
+T15360b.hs:16:14: error:
+ • Expected kind ‘* -> k2’, but ‘Constraint’ has kind ‘*’
+ • In the first argument of ‘Proxy’, namely ‘(Constraint Bool)’
+ In the type signature: z :: Proxy (Constraint Bool)
+
+T15360b.hs:19:14: error:
+ • Expected kind ‘* -> k1’, but ‘'[]’ has kind ‘[k0]’
+ • In the first argument of ‘Proxy’, namely ‘('[] Int)’
+ In the type signature: w :: Proxy ('[] Int)
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 948c7db8d7..249493e0ff 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -419,6 +419,8 @@ test('T15321', normal, compile_fail, [''])
test('T15324', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T15331', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T15365', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('T15360a', normal, compile, [''])
+test('T15360b', normal, compile_fail, [''])
# Note: T9693 should be only_ways(['ghci']) once it's fixed.
test('T9693', expect_broken(9693), ghci_script, ['T9693.script'])
test('T14471', normal, compile, [''])