summaryrefslogtreecommitdiff
path: root/testsuite/tests/th
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2021-04-25 08:14:03 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-04-27 00:00:43 -0400
commitdd121fa178c29a154233e95a15c755d0ca7cbdcc (patch)
treed5f8ef872539dad8c56eeedc4e583130565931f9 /testsuite/tests/th
parentd9ceb2fb51b037a330a6cfaf129c24ea7f1ac644 (diff)
downloadhaskell-dd121fa178c29a154233e95a15c755d0ca7cbdcc.tar.gz
Pretty-print HsArgPar applications correctly (#19737)
Previously, the `Outputable` instance for `HsArg` was being used to pretty-print each `HsArgPar` in a list of `HsArg`s individually, which simply doesn't work. In lieu of the `Outputable` instance, we now use a dedicated `pprHsArgsApp` function to print a list of `HsArg`s as a single unit. I have also added documentation to the `Outputable` instance for `HsArg` to more clearly signpost that it is only suitable for debug pretty-printing. Fixes #19737.
Diffstat (limited to 'testsuite/tests/th')
-rw-r--r--testsuite/tests/th/T19737.hs14
-rw-r--r--testsuite/tests/th/T19737.stderr20
-rw-r--r--testsuite/tests/th/all.T1
3 files changed, 35 insertions, 0 deletions
diff --git a/testsuite/tests/th/T19737.hs b/testsuite/tests/th/T19737.hs
new file mode 100644
index 0000000000..72ec1fe053
--- /dev/null
+++ b/testsuite/tests/th/T19737.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -ddump-splices #-}
+module T19737 where
+
+import Language.Haskell.TH
+
+type family T a
+
+$(pure [ TySynInstD (TySynEqn Nothing (ConT ''T `AppT` ConT ''Char) (ConT ''Char))
+ , TySynInstD (TySynEqn Nothing (ParensT (ConT ''T) `AppT` ConT ''Int) (ConT ''Int))
+ , TySynInstD (TySynEqn Nothing (ParensT (ConT ''T `AppT` ConT ''Bool)) (ConT ''Bool))
+ , TySynInstD (TySynEqn Nothing (ParensT (ParensT (ConT ''T `AppT` ParensT (ConT ''Double)))) (ConT ''Double))
+ ])
diff --git a/testsuite/tests/th/T19737.stderr b/testsuite/tests/th/T19737.stderr
new file mode 100644
index 0000000000..ba1465b26a
--- /dev/null
+++ b/testsuite/tests/th/T19737.stderr
@@ -0,0 +1,20 @@
+T19737.hs:(10,2)-(14,9): Splicing declarations
+ pure
+ [TySynInstD
+ (TySynEqn Nothing (ConT ''T `AppT` ConT ''Char) (ConT ''Char)),
+ TySynInstD
+ (TySynEqn
+ Nothing (ParensT (ConT ''T) `AppT` ConT ''Int) (ConT ''Int)),
+ TySynInstD
+ (TySynEqn
+ Nothing (ParensT (ConT ''T `AppT` ConT ''Bool)) (ConT ''Bool)),
+ TySynInstD
+ (TySynEqn
+ Nothing
+ (ParensT (ParensT (ConT ''T `AppT` ParensT (ConT ''Double))))
+ (ConT ''Double))]
+ ======>
+ type instance T Char = Char
+ type instance (T) Int = Int
+ type instance (T Bool) = Bool
+ type instance ((T (Double))) = Double
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 857c9f3659..fb3bc7fb49 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -523,3 +523,4 @@ test('T19363', normal, compile_and_run, [''])
test('T19377', normal, compile, [''])
test('T17804', normal, compile, [''])
test('T19470', only_ways(['ghci']), ghci_script, ['T19470.script'])
+test('T19737', normal, compile, [''])