[Git][ghc/ghc][master] unboxedSum{Type,Data}Name: Use GHC.Types as the module

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat May 4 10:04:18 UTC 2024



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


Commits:
fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00
unboxedSum{Type,Data}Name: Use GHC.Types as the module

Unboxed sum constructors are now defined in the `GHC.Types` module, so if you
manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like:

```hs
GHC.Types.Sum2#
```

The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly
believes that unboxed sum constructors are defined in `GHC.Prim`, so
`unboxedSumTypeName 2` would return an entirely different `Name`:

```hs
GHC.Prim.(#|#)
```

This is a problem for Template Haskell users, as it means that they can't be
sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.)

This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use
`GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the
`unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums
(`Sum<N>#`) as the `OccName`.

Fixes #24750.

- - - - -


3 changed files:

- libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs
- + testsuite/tests/quotes/T24750.hs
- testsuite/tests/quotes/all.T


Changes:

=====================================
libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs
=====================================
@@ -1955,7 +1955,7 @@ unboxedSumDataName alt arity
 
   | otherwise
   = Name (mkOccName sum_occ)
-         (NameG DataName (mkPkgName "ghc-prim") (mkModName "GHC.Prim"))
+         (NameG DataName (mkPkgName "ghc-prim") (mkModName "GHC.Types"))
 
   where
     prefix     = "unboxedSumDataName: "
@@ -1974,11 +1974,11 @@ unboxedSumTypeName arity
 
   | otherwise
   = Name (mkOccName sum_occ)
-         (NameG TcClsName (mkPkgName "ghc-prim") (mkModName "GHC.Prim"))
+         (NameG TcClsName (mkPkgName "ghc-prim") (mkModName "GHC.Types"))
 
   where
     -- Synced with the definition of mkSumTyConOcc in GHC.Builtin.Types
-    sum_occ = '(' : '#' : replicate (arity - 1) '|' ++ "#)"
+    sum_occ = "Sum" ++ show arity ++ "#"
 
 -----------------------------------------------------
 --              Locations


=====================================
testsuite/tests/quotes/T24750.hs
=====================================
@@ -0,0 +1,35 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE TemplateHaskellQuotes #-}
+{-# LANGUAGE UnboxedTuples #-}
+-- A regression test for #24750. This test ensures that a family of functions
+-- from the `template-haskell` library (tupeTypeName, tupleDataName, etc.)
+-- returns the same Names as when you manually quote the names using
+-- TemplateHaskellQuotes.
+module Main (main) where
+
+import Control.Monad (unless)
+import GHC.Tuple (Tuple2)
+import GHC.Types (Sum2#, Tuple2#)
+import Language.Haskell.TH
+
+test :: Name -> Name -> IO ()
+test n1 n2 =
+  unless (n1 == n2) $
+    fail $ unlines
+      [ "Names are not equal"
+      , "LHS name: " ++ show n1
+      , "RHS name: " ++ show n2
+      ]
+
+main :: IO ()
+main = do
+  test (tupleTypeName 2) ''(,)
+  test (tupleTypeName 2) ''Tuple2
+  test (tupleDataName 2) '(,)
+  test (unboxedTupleTypeName 2) ''(#,#)
+  test (unboxedTupleTypeName 2) ''Tuple2#
+  test (unboxedTupleDataName 2) '(#,#)
+  test (unboxedSumTypeName 2) ''Sum2#
+  -- There is currently no way to manually quote an unboxed sum data constructor
+  -- Name, as you cannot write unboxed sum data constructors in prefix form. As
+  -- such, a test case for `unboxedSumDataName` is omitted.


=====================================
testsuite/tests/quotes/all.T
=====================================
@@ -42,3 +42,4 @@ test('T20688', normal, compile, ['-Wimplicit-lift -Werror'])
 test('T20893', normal, compile_and_run, [''])
 test('T21619', normal, compile, [''])
 test('T20472_quotes', normal, compile, [''])
+test('T24750', normal, compile_and_run, [''])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc24c5cf6c62ca9e3c8d236656e139676df65034
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/20240504/25be2698/attachment-0001.html>


More information about the ghc-commits mailing list