[Git][ghc/ghc][master] compiler: Fix pretty printing of ticked prefix constructors (#24237)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Aug 21 07:18:36 UTC 2024



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


Commits:
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -


4 changed files:

- compiler/GHC/Iface/Type.hs
- + testsuite/tests/printer/T24237.hs
- + testsuite/tests/printer/T24237.stderr
- testsuite/tests/printer/all.T


Changes:

=====================================
compiler/GHC/Iface/Type.hs
=====================================
@@ -1847,17 +1847,16 @@ ppr_iface_tc_app pp ctxt_prec tc tys =
      | tc `ifaceTyConHasKey` liftedTypeKindTyConKey
      -> ppr_kind_type ctxt_prec
 
-     | not (isSymOcc (nameOccName (ifaceTyConName tc)))
-     -> pprIfacePrefixApp ctxt_prec (ppr tc) (map (pp appPrec) tys)
+     | isSymOcc (nameOccName (ifaceTyConName tc))
 
-     | [ ty1@(_, Required), ty2@(_, Required) ] <- tys
+     , [ ty1@(_, Required), ty2@(_, Required) ] <- tys
          -- Infix, two visible arguments (we know nothing of precedence though).
          -- Don't apply this special case if one of the arguments is invisible,
          -- lest we print something like (@LiftedRep -> @LiftedRep) (#15941).
-     -> pprIfaceInfixApp ctxt_prec (ppr tc) (pp opPrec ty1) (pp opPrec ty2)
+     -> pprIfaceInfixApp ctxt_prec (pprIfaceTyCon tc) (pp opPrec ty1) (pp opPrec ty2)
 
      | otherwise
-     -> pprIfacePrefixApp ctxt_prec (parens (ppr tc)) (map (pp appPrec) tys)
+     -> pprIfacePrefixApp ctxt_prec (pprParendIfaceTyCon tc) (map (pp appPrec) tys)
 
 data TupleOrSum = IsSum | IsTuple TupleSort
   deriving (Eq)
@@ -2070,7 +2069,18 @@ instance Outputable IfLclName where
   ppr = ppr . ifLclNameFS
 
 instance Outputable IfaceTyCon where
-  ppr tc = pprPromotionQuote tc <> ppr (ifaceTyConName tc)
+  ppr = pprIfaceTyCon
+
+-- | Print an `IfaceTyCon` with a promotion tick if needed, without parens,
+-- suitable for use in infix contexts
+pprIfaceTyCon :: IfaceTyCon -> SDoc
+pprIfaceTyCon tc = pprPromotionQuote tc <> ppr (ifaceTyConName tc)
+
+-- | Print an `IfaceTyCon` with a promotion tick if needed, possibly with parens,
+-- suitable for use in prefix contexts
+pprParendIfaceTyCon :: IfaceTyCon -> SDoc
+pprParendIfaceTyCon tc = pprPromotionQuote tc <> pprPrefixVar (isSymOcc (nameOccName tc_name)) (ppr tc_name)
+  where tc_name = ifaceTyConName tc
 
 instance Outputable IfaceTyConInfo where
   ppr (IfaceTyConInfo { ifaceTyConIsPromoted = prom


=====================================
testsuite/tests/printer/T24237.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds #-}
+{-# OPTIONS_GHC -fprint-redundant-promotion-ticks #-}
+module T24237 where
+
+import Data.Proxy
+
+foo :: Proxy '(:)
+foo = ()


=====================================
testsuite/tests/printer/T24237.stderr
=====================================
@@ -0,0 +1,7 @@
+T24237.hs:8:7: error: [GHC-83865]
+    • Couldn't match expected type ‘Proxy '(:)’ with actual type ‘()’
+    • In the expression: ()
+      In an equation for ‘foo’: foo = ()
+    • Relevant bindings include
+        foo :: Proxy '(:) (bound at T24237.hs:8:1)
+


=====================================
testsuite/tests/printer/all.T
=====================================
@@ -210,3 +210,5 @@ test('Test24753', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24753'])
 test('Test24771', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24771'])
 test('Test24159', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24159'])
 test('Test25132', [ignore_stderr, req_ppr_deps], makefile_test, ['Test25132'])
+
+test('T24237', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f972bfb36866d5df39b4771c0e1c35bce5daf2c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f972bfb36866d5df39b4771c0e1c35bce5daf2c
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/20240821/b70bae8d/attachment-0001.html>


More information about the ghc-commits mailing list