[Git][ghc/ghc][master] Rename Solo# data constructor to MkSolo# (#24673)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue May 7 18:40:34 UTC 2024



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


Commits:
3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00
Rename Solo# data constructor to MkSolo# (#24673)

- data Solo# a = (# a #)
+ data Solo# a = MkSolo# a

And `(# foo #)` syntax now becomes just a syntactic
sugar for `MkSolo# a`.

- - - - -


11 changed files:

- compiler/GHC/Builtin/Types.hs
- libraries/ghc-boot/GHC/Utils/Encoding.hs
- libraries/ghc-experimental/src/Data/Tuple/Experimental.hs
- libraries/ghc-prim/GHC/Types.hs
- libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/ghci/scripts/ListTuplePunsPpr.script
- testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/th/TH_tuple1.stdout


Changes:

=====================================
compiler/GHC/Builtin/Types.hs
=====================================
@@ -1015,7 +1015,7 @@ mkUnboxedTupleStr ns 0
   | isDataConNameSpace ns = "(##)"
   | otherwise             = "Unit#"
 mkUnboxedTupleStr ns 1
-  | isDataConNameSpace ns = "(# #)"  -- See Note [One-tuples]
+  | isDataConNameSpace ns = "MkSolo#"  -- See Note [One-tuples]
   | otherwise             = "Solo#"
 mkUnboxedTupleStr ns ar
   | isDataConNameSpace ns = "(#" ++ commas ar ++ "#)"


=====================================
libraries/ghc-boot/GHC/Utils/Encoding.hs
=====================================
@@ -79,7 +79,7 @@ The basic encoding scheme is this.
         :+              ZCzp
         ()              Z0T     0-tuple
         (,,,,)          Z5T     5-tuple
-        (# #)           Z1H     unboxed 1-tuple (note the space)
+        (##)            Z0H     unboxed 0-tuple
         (#,,,,#)        Z5H     unboxed 5-tuple
 -}
 
@@ -212,7 +212,6 @@ decode_tuple d rest
     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
     go 0 ('T':rest)     = "()" ++ zDecodeString rest
     go n ('T':rest)     = '(' : replicate (n-1) ',' ++ ")" ++ zDecodeString rest
-    go 1 ('H':rest)     = "(# #)" ++ zDecodeString rest
     go n ('H':rest)     = '(' : '#' : replicate (n-1) ',' ++ "#)" ++ zDecodeString rest
     go n other = error ("decode_tuple: " ++ show n ++ ' ':other)
 
@@ -223,15 +222,13 @@ for 3-tuples or unboxed 3-tuples respectively.  No other encoding starts
         Z<digit>
 
 * "(##)" is the tycon for an unboxed 0-tuple
-* "(# #)" is the tycon for an unboxed 1-tuple
 
-* "()" is the tycon for a boxed 0-tuple.
+* "()" is the tycon for a boxed 0-tuple
 -}
 
 maybe_tuple :: UserString -> Maybe EncodedString
 
 maybe_tuple "(##)" = Just("Z0H")
-maybe_tuple "(# #)" = Just("Z1H")
 maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
                                  (n, '#' : ')' : _) -> Just ('Z' : shows (n+1) "H")
                                  _                  -> Nothing


=====================================
libraries/ghc-experimental/src/Data/Tuple/Experimental.hs
=====================================
@@ -21,7 +21,7 @@ module Data.Tuple.Experimental (
 
   -- * Unboxed tuples
   Unit#,
-  Solo#,
+  Solo#(..),
   Tuple0#,
   Tuple1#,
   Tuple2#,


=====================================
libraries/ghc-prim/GHC/Types.hs
=====================================
@@ -65,7 +65,7 @@ module GHC.Types (
 
         -- * Unboxed tuples
         Unit#,
-        Solo#,
+        Solo#(..),
         Tuple0#,
         Tuple1#,
         Tuple2#,
@@ -889,7 +889,7 @@ type Unit# :: TYPE (TupleRep '[])
 data Unit# = (# #)
 
 type Solo# :: TYPE rep -> TYPE (TupleRep '[rep])
-data Solo# a = (# a #)
+data Solo# a = MkSolo# a
 
 type Tuple0# = Unit#
 type Tuple1# = Solo#


=====================================
libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs
=====================================
@@ -1933,9 +1933,7 @@ mk_tup_name n space boxed
       | space == DataName = "MkSolo"
       | otherwise = "Solo"
 
-    unboxed_solo
-      | space == DataName = "(# #)"
-      | otherwise = "Solo#"
+    unboxed_solo = solo ++ "#"
 
 -- Unboxed sum data and type constructors
 -- | Unboxed sum data constructor


=====================================
testsuite/tests/core-to-stg/T24124.stderr
=====================================
@@ -24,7 +24,7 @@ T15226b.testFun1
         case y of conrep {
         __DEFAULT ->
         case T15226b.MkStrictPair [sat conrep] of sat {
-        __DEFAULT -> (# #) [sat];
+        __DEFAULT -> MkSolo# [sat];
         };
         };
         };


=====================================
testsuite/tests/ghci/scripts/ListTuplePunsPpr.script
=====================================
@@ -1,6 +1,7 @@
 
-:set -XUnboxedTuples -XNoListTuplePuns -XDataKinds
+:set -XUnboxedTuples -XMagicHash -XNoListTuplePuns -XDataKinds
 import GHC.Tuple (Solo (MkSolo))
+import Data.Tuple.Experimental (Solo# (MkSolo#))
 
 :i ()
 :i (##)
@@ -26,3 +27,5 @@ f i (j, k) = i + j + k :: Int
 :t f
 :t (\ (_, _) -> ())
 :t (\ (MkSolo _) -> ())
+:i Solo#
+:t MkSolo#


=====================================
testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout
=====================================
@@ -75,13 +75,17 @@ data Tuple2# a b = (#,#) a b
 (Int, Int) :: Tuple2 (*) (*)
 type T :: Tuple2 (*) (*)
 type T = (Int, Int) :: Tuple2 (*) (*)
-  	-- Defined at <interactive>:18:1
+  	-- Defined at <interactive>:19:1
 type S :: Solo (*)
 type S = MkSolo Int :: Solo (*)
-  	-- Defined at <interactive>:19:1
+  	-- Defined at <interactive>:20:1
 type L :: List (*)
 type L = [Int] :: List (*)
-  	-- Defined at <interactive>:20:1
+  	-- Defined at <interactive>:21:1
 f :: Int -> Tuple2 Int Int -> Int
 (\ (_, _) -> ()) :: Tuple2 a b -> Unit
 (\ (MkSolo _) -> ()) :: Solo a -> Unit
+type Solo# :: * -> TYPE (GHC.Types.TupleRep [GHC.Types.LiftedRep])
+data Solo# a = MkSolo# a
+  	-- Defined in ‘GHC.Types’
+MkSolo# :: a -> Solo# a


=====================================
testsuite/tests/interface-stability/ghc-experimental-exports.stdout
=====================================
@@ -2633,7 +2633,7 @@ module Data.Tuple.Experimental where
   type Solo :: * -> *
   data Solo a = MkSolo a
   type Solo# :: forall (k :: GHC.Types.RuntimeRep). TYPE k -> TYPE (GHC.Types.TupleRep '[k])
-  data Solo# a = ...
+  data Solo# a = MkSolo# a
   type Tuple0 :: *
   type Tuple0 = ()
   type Tuple0# :: GHC.Types.ZeroBitType


=====================================
testsuite/tests/simplStg/should_compile/T15226b.stderr
=====================================
@@ -20,7 +20,7 @@ T15226b.bar1
           sat [Occ=Once1] :: T15226b.Str (GHC.Internal.Maybe.Maybe a)
           [LclId] =
               T15226b.Str! [sat];
-        } in  (# #) [sat];
+        } in  MkSolo# [sat];
         };
 
 T15226b.bar


=====================================
testsuite/tests/th/TH_tuple1.stdout
=====================================
@@ -6,5 +6,5 @@ GHC.Tuple.MkSolo 1 :: GHC.Tuple.Solo GHC.Num.Integer.Integer
 SigE (AppE (AppE (ConE GHC.Types.(#,#)) (LitE (IntegerL 1))) (LitE (IntegerL 2))) (AppT (AppT (ConT GHC.Types.Tuple2#) (ConT GHC.Num.Integer.Integer)) (ConT GHC.Num.Integer.Integer))
 GHC.Types.(#,#) 1 2 :: GHC.Types.Tuple2# GHC.Num.Integer.Integer
                                          GHC.Num.Integer.Integer
-SigE (AppE (ConE GHC.Types.(# #)) (LitE (IntegerL 1))) (AppT (ConT GHC.Types.Solo#) (ConT GHC.Num.Integer.Integer))
-GHC.Types.(# #) 1 :: GHC.Types.Solo# GHC.Num.Integer.Integer
+SigE (AppE (ConE GHC.Types.MkSolo#) (LitE (IntegerL 1))) (AppT (ConT GHC.Types.Solo#) (ConT GHC.Num.Integer.Integer))
+GHC.Types.MkSolo# 1 :: GHC.Types.Solo# GHC.Num.Integer.Integer



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b51995c158fe19d48839b92cf1ff78ce7825ce4
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/20240507/97edbffe/attachment-0001.html>


More information about the ghc-commits mailing list