[Git][ghc/ghc][master] EPA: Remove parenthesizeHsType

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Nov 24 13:30:53 UTC 2023



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


Commits:
34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00
EPA: Remove parenthesizeHsType

This is called from PostProcess.hs, and adds spurious parens.
With the looser version of exact printing we had before we could
tolerate this, as they would be swallowed by the original at the same
place.

But with the next change (remove EpAnnNotUsed) they result in
duplicates in the output.

For Darwin build:

Metric Increase:
    MultiLayerModulesTH_OneShot

- - - - -


3 changed files:

- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- testsuite/tests/parser/should_fail/unpack_inside_type.stderr


Changes:

=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -541,7 +541,7 @@ mkHsOpTy prom ty1 op ty2 = HsOpTy noAnn prom ty1 op ty2
 
 mkHsAppTy :: LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
 mkHsAppTy t1 t2
-  = addCLocA t1 t2 (HsAppTy noExtField t1 (parenthesizeHsType appPrec t2))
+  = addCLocA t1 t2 (HsAppTy noExtField t1 t2)
 
 mkHsAppTys :: LHsType (GhcPass p) -> [LHsType (GhcPass p)]
            -> LHsType (GhcPass p)


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -263,7 +263,7 @@ mkHsAppType :: LHsExpr GhcRn -> LHsWcType GhcRn -> LHsExpr GhcRn
 mkHsAppType e t = addCLocA t_body e (HsAppType noExtField e noHsTok paren_wct)
   where
     t_body    = hswc_body t
-    paren_wct = t { hswc_body = parenthesizeHsType appPrec t_body }
+    paren_wct = t { hswc_body = t_body }
 
 mkHsAppTypes :: LHsExpr GhcRn -> [LHsWcType GhcRn] -> LHsExpr GhcRn
 mkHsAppTypes = foldl' mkHsAppType
@@ -628,9 +628,9 @@ nlHsTyVar :: IsSrcSpanAnn p a
 nlHsFunTy :: LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
 nlHsParTy :: LHsType (GhcPass p)                        -> LHsType (GhcPass p)
 
-nlHsAppTy f t = noLocA (HsAppTy noExtField f (parenthesizeHsType appPrec t))
+nlHsAppTy f t = noLocA (HsAppTy noExtField f t)
 nlHsTyVar p x = noLocA (HsTyVar noAnn p (noLocA x))
-nlHsFunTy a b = noLocA (HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) (parenthesizeHsType funPrec a) b)
+nlHsFunTy a b = noLocA (HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) a b)
 nlHsParTy t   = noLocA (HsParTy noAnn t)
 
 nlHsTyConApp :: IsSrcSpanAnn p a
@@ -647,14 +647,14 @@ nlHsTyConApp prom fixity tycon tys
     mk_app :: LHsType (GhcPass p) -> LHsTypeArg (GhcPass p) -> LHsType (GhcPass p)
     mk_app fun@(L _ (HsOpTy {})) arg = mk_app (noLocA $ HsParTy noAnn fun) arg
       -- parenthesize things like `(A + B) C`
-    mk_app fun (HsValArg ty) = noLocA (HsAppTy noExtField fun (parenthesizeHsType appPrec ty))
-    mk_app fun (HsTypeArg at ki) = noLocA (HsAppKindTy noExtField fun at (parenthesizeHsType appPrec ki))
+    mk_app fun (HsValArg ty) = noLocA (HsAppTy noExtField fun ty)
+    mk_app fun (HsTypeArg at ki) = noLocA (HsAppKindTy noExtField fun at ki)
     mk_app fun (HsArgPar _) = noLocA (HsParTy noAnn fun)
 
 nlHsAppKindTy ::
   LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p)
 nlHsAppKindTy f k
-  = noLocA (HsAppKindTy noExtField f noHsTok (parenthesizeHsType appPrec k))
+  = noLocA (HsAppKindTy noExtField f noHsTok k)
 
 {-
 Tuples.  All these functions are *pre-typechecker* because they lack


=====================================
testsuite/tests/parser/should_fail/unpack_inside_type.stderr
=====================================
@@ -2,6 +2,6 @@
 unpack_inside_type.hs:3:25: error: [GHC-18932]
     • Unexpected UNPACK annotation: {-# UNPACK #-}Int
       UNPACK annotation cannot appear nested inside a type
-    • In the first argument of ‘Maybe’, namely ‘({-# UNPACK #-}Int)’
-      In the type ‘Maybe ({-# UNPACK #-}Int)’
+    • In the first argument of ‘Maybe’, namely ‘{-# UNPACK #-}Int’
+      In the type ‘Maybe {-# UNPACK #-}Int’
       In the definition of data constructor ‘T’



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34d863153155284c3e389d258f454490c205b58f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34d863153155284c3e389d258f454490c205b58f
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/20231124/2f8a93cc/attachment-0001.html>


More information about the ghc-commits mailing list