[Git][ghc/ghc][master] Type operators in promoteOccName (#24570)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Mar 21 02:45:58 UTC 2024



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


Commits:
da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00
Type operators in promoteOccName (#24570)

Type operators differ from term operators in that they are lexically
classified as (type) constructors, not as (type) variables.

Prior to this change, promoteOccName did not account for this
difference, causing a scoping issue that affected RequiredTypeArguments.

  type (!@#) = Bool
  f = idee (!@#)      -- Not in scope: ‘!@#’  (BUG)

Now we have a special case in promoteOccName to account for this.

- - - - -


3 changed files:

- compiler/GHC/Types/Name/Occurrence.hs
- + testsuite/tests/vdq-rta/should_compile/T24570.hs
- testsuite/tests/vdq-rta/should_compile/all.T


Changes:

=====================================
compiler/GHC/Types/Name/Occurrence.hs
=====================================
@@ -516,7 +516,9 @@ demoteOccTvName (OccName space name) = do
 -- See Note [Promotion] in GHC.Rename.Env.
 promoteOccName :: OccName -> Maybe OccName
 promoteOccName (OccName space name) = do
-  space' <- promoteNameSpace space
+  promoted_space <- promoteNameSpace space
+  let tyop   = isTvNameSpace promoted_space && isLexVarSym name
+      space' = if tyop then tcClsName else promoted_space   -- special case for type operators (#24570)
   return $ OccName space' name
 
 {- | Other names in the compiler add additional information to an OccName.


=====================================
testsuite/tests/vdq-rta/should_compile/T24570.hs
=====================================
@@ -0,0 +1,19 @@
+{-# LANGUAGE GHC2024 #-}
+{-# LANGUAGE RequiredTypeArguments #-}
+
+module T24570 where
+
+import Language.Haskell.TH
+
+idee :: forall a -> a -> a
+idee _ x = x
+
+type (:!@#) = Bool
+
+f :: Bool -> Bool
+f = idee (:!@#)
+
+type (!@#) = Bool
+
+g :: Bool -> Bool
+g = idee (!@#)
\ No newline at end of file


=====================================
testsuite/tests/vdq-rta/should_compile/all.T
=====================================
@@ -22,6 +22,7 @@ test('T23739_sizeOf', normal, compile, [''])
 test('T23739_symbolVal', normal, compile, [''])
 test('T23739_typeRep', normal, compile, [''])
 test('T23739_nested', normal, compile, [''])
+test('T24570', normal, compile, [''])
 
 test('T22326_th_dump1', req_th, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T23739_th_dump1', req_th, compile, ['-v0 -ddump-splices -dsuppress-uniques'])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da2a10ceab7498fbbd5723dee0393ce75f2bb562
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/20240320/52cdf10e/attachment-0001.html>


More information about the ghc-commits mailing list