[Git][ghc/ghc][master] Add missing parenthesizeHsType in cvtSigTypeKind

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Jan 18 06:57:22 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
4efee43d by Ryan Scott at 2023-01-18T01:56:59-05:00
Add missing parenthesizeHsType in cvtSigTypeKind

We need to ensure that the output of `cvtSigTypeKind` is parenthesized (at
precedence `sigPrec`) so that any type signatures with an outermost, explicit
kind signature can parse correctly.

Fixes #22784.

- - - - -


4 changed files:

- compiler/GHC/ThToHs.hs
- + testsuite/tests/th/T22784.hs
- + testsuite/tests/th/T22784.stderr
- testsuite/tests/th/all.T


Changes:

=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -1556,7 +1556,7 @@ cvtSigType = cvtSigTypeKind TypeLevel
 cvtSigTypeKind :: TypeOrKind -> TH.Type -> CvtM (LHsSigType GhcPs)
 cvtSigTypeKind typeOrKind ty = do
   ty' <- cvtTypeKind typeOrKind ty
-  pure $ hsTypeToHsSigType ty'
+  pure $ hsTypeToHsSigType $ parenthesizeHsType sigPrec ty'
 
 cvtTypeKind :: TypeOrKind -> TH.Type -> CvtM (LHsType GhcPs)
 cvtTypeKind typeOrKind ty


=====================================
testsuite/tests/th/T22784.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T22784 where
+
+import Data.Kind
+
+$([d| f :: (Bool :: Type)
+      f = True |])


=====================================
testsuite/tests/th/T22784.stderr
=====================================
@@ -0,0 +1,6 @@
+T22784.hs:(6,2)-(7,18): Splicing declarations
+    [d| f :: (Bool :: Type)
+        f = True |]
+  ======>
+    f :: (Bool :: Type)
+    f = True


=====================================
testsuite/tests/th/all.T
=====================================
@@ -555,4 +555,5 @@ test('Lift_ByteArray', normal, compile_and_run, [''])
 test('T21920', normal, compile_and_run, [''])
 test('T21723', normal, compile_and_run, [''])
 test('T21942', normal, compile_and_run, [''])
-test('TH_fun_par', normal, compile, [''])
\ No newline at end of file
+test('T22784', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('TH_fun_par', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4efee43db5090aac4dde1293357bdb548ae71c24

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4efee43db5090aac4dde1293357bdb548ae71c24
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230118/185cbf70/attachment-0001.html>


More information about the ghc-commits mailing list