[Git][ghc/ghc][wip/T18612] Make {hsExpr, hsType, pat}NeedsParens aware of boxed 1-tuples

Ryan Scott gitlab at gitlab.haskell.org
Wed Aug 26 23:17:11 UTC 2020



Ryan Scott pushed to branch wip/T18612 at Glasgow Haskell Compiler / GHC


Commits:
222a8788 by Ryan Scott at 2020-08-26T19:16:56-04:00
Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples

`hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens`
previously assumed that all uses of explicit tuples in the source
syntax never need to be parenthesized. This is true save for one
exception: boxed one-tuples, which use the `Solo` data type from
`GHC.Tuple` instead of special tuple syntax. This patch adds the
necessary logic to the three `*NeedsParens` functions to handle
`Solo` correctly.

Fixes #18612.

- - - - -


6 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- + testsuite/tests/th/T18612.hs
- + testsuite/tests/th/T18612.stderr
- testsuite/tests/th/all.T


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -1320,6 +1320,11 @@ hsExprNeedsParens p = go
     go (NegApp{})                     = p > topPrec
     go (SectionL{})                   = True
     go (SectionR{})                   = True
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Identity (Solo x)`, not `Identity Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go (ExplicitTuple _ [L _ Present{}] Boxed)
+                                      = p >= appPrec
     go (ExplicitTuple{})              = False
     go (ExplicitSum{})                = False
     go (HsLam{})                      = p > topPrec


=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -857,7 +857,12 @@ patNeedsParens p = go
     go (BangPat {})      = False
     go (ParPat {})       = False
     go (AsPat {})        = False
-    go (TuplePat {})     = False
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Identity (Solo x)`, not `Identity Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go (TuplePat _ [_] Boxed)
+                         = p >= appPrec
+    go (TuplePat{})      = False
     go (SumPat {})       = False
     go (ListPat {})      = False
     go (LitPat _ l)      = hsLitNeedsParens p l


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -1979,6 +1979,15 @@ hsTypeNeedsParens p = go_hs_ty
     go_hs_ty (HsRecTy{})              = False
     go_hs_ty (HsTyVar{})              = False
     go_hs_ty (HsFunTy{})              = p >= funPrec
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Identity (Solo x)`, not `Identity Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go_hs_ty (HsTupleTy _ con [L _ ty])
+      = case con of
+          HsBoxedTuple               -> p >= appPrec
+          HsBoxedOrConstraintTuple   -> p >= appPrec
+          HsConstraintTuple          -> go_hs_ty ty
+          HsUnboxedTuple             -> False
     go_hs_ty (HsTupleTy{})            = False
     go_hs_ty (HsSumTy{})              = False
     go_hs_ty (HsKindSig{})            = p >= sigPrec
@@ -1986,6 +1995,11 @@ hsTypeNeedsParens p = go_hs_ty
     go_hs_ty (HsIParamTy{})           = p > topPrec
     go_hs_ty (HsSpliceTy{})           = False
     go_hs_ty (HsExplicitListTy{})     = False
+    -- Special-case unary boxed tuple applications so that they are
+    -- parenthesized as `Proxy ('Solo x)`, not `Proxy 'Solo x` (#18612)
+    -- See Note [One-tuples] in GHC.Builtin.Types
+    go_hs_ty (HsExplicitTupleTy _ [_])
+                                      = p >= appPrec
     go_hs_ty (HsExplicitTupleTy{})    = False
     go_hs_ty (HsTyLit{})              = False
     go_hs_ty (HsWildCardTy{})         = False


=====================================
testsuite/tests/th/T18612.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS_GHC -ddump-splices #-}
+module T18612 where
+
+import Data.Functor.Identity
+import Data.Proxy
+import Language.Haskell.TH
+
+f :: $(arrowT `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0)))
+              `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0))))
+f $(conP 'Identity [tupP [tupP []]]) = $(conE 'Identity `appE` tupE [tupE []])
+
+type G = $(conT ''Proxy `appT` (promotedTupleT 1 `appT` (tupleT 0)))


=====================================
testsuite/tests/th/T18612.stderr
=====================================
@@ -0,0 +1,13 @@
+T18612.hs:14:11-68: Splicing type
+    conT ''Proxy `appT` (promotedTupleT 1 `appT` (tupleT 0))
+  ======>
+    Proxy ('Solo ())
+T18612.hs:(10,7)-(11,75): Splicing type
+    arrowT `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0)))
+      `appT` (conT ''Identity `appT` (tupleT 1 `appT` (tupleT 0)))
+  ======>
+    Identity (Solo ()) -> Identity (Solo ())
+T18612.hs:12:4-36: Splicing pattern
+    conP 'Identity [tupP [tupP []]] ======> Identity (Solo())
+T18612.hs:12:41-78: Splicing expression
+    conE 'Identity `appE` tupE [tupE []] ======> Identity (Solo ())


=====================================
testsuite/tests/th/all.T
=====================================
@@ -513,3 +513,4 @@ test('T18102b', extra_files(['T18102b_aux.hs']), compile_and_run, [''])
 test('T18121', normal, compile, [''])
 test('T18123', normal, compile, [''])
 test('T18388', normal, compile, [''])
+test('T18612', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/222a878875b0e093e82f81d6f83fa39ac42d53b5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/222a878875b0e093e82f81d6f83fa39ac42d53b5
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/20200826/a743539a/attachment-0001.html>


More information about the ghc-commits mailing list