From 3b51995c158fe19d48839b92cf1ff78ce7825ce4 Mon Sep 17 00:00:00 2001 From: Andrei Borzenkov <andreyborzenkov2002@gmail.com> Date: Fri, 26 Apr 2024 12:17:09 +0400 Subject: [PATCH] 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`. --- compiler/GHC/Builtin/Types.hs | 2 +- libraries/ghc-boot/GHC/Utils/Encoding.hs | 7 ++----- .../ghc-experimental/src/Data/Tuple/Experimental.hs | 2 +- libraries/ghc-prim/GHC/Types.hs | 4 ++-- .../template-haskell/Language/Haskell/TH/Lib/Syntax.hs | 4 +--- testsuite/tests/core-to-stg/T24124.stderr | 2 +- testsuite/tests/ghci/scripts/ListTuplePunsPpr.script | 5 ++++- testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout | 10 +++++++--- .../ghc-experimental-exports.stdout | 2 +- testsuite/tests/simplStg/should_compile/T15226b.stderr | 2 +- testsuite/tests/th/TH_tuple1.stdout | 4 ++-- 11 files changed, 23 insertions(+), 21 deletions(-) diff --git a/compiler/GHC/Builtin/Types.hs b/compiler/GHC/Builtin/Types.hs index 9982007cfcbb..8fbc6e61f65f 100644 --- a/compiler/GHC/Builtin/Types.hs +++ b/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 ++ "#)" diff --git a/libraries/ghc-boot/GHC/Utils/Encoding.hs b/libraries/ghc-boot/GHC/Utils/Encoding.hs index e454d47758f0..5b0f7d517304 100644 --- a/libraries/ghc-boot/GHC/Utils/Encoding.hs +++ b/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 diff --git a/libraries/ghc-experimental/src/Data/Tuple/Experimental.hs b/libraries/ghc-experimental/src/Data/Tuple/Experimental.hs index 90bcd692cb74..4b9d8f3ec960 100644 --- a/libraries/ghc-experimental/src/Data/Tuple/Experimental.hs +++ b/libraries/ghc-experimental/src/Data/Tuple/Experimental.hs @@ -21,7 +21,7 @@ module Data.Tuple.Experimental ( -- * Unboxed tuples Unit#, - Solo#, + Solo#(..), Tuple0#, Tuple1#, Tuple2#, diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs index c3a9fe623149..cb52a59f48b8 100644 --- a/libraries/ghc-prim/GHC/Types.hs +++ b/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# diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs index 64b9655de53f..8d080fef9bb5 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Lib/Syntax.hs +++ b/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 diff --git a/testsuite/tests/core-to-stg/T24124.stderr b/testsuite/tests/core-to-stg/T24124.stderr index b30bdb934336..baf21e99c2d1 100644 --- a/testsuite/tests/core-to-stg/T24124.stderr +++ b/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]; }; }; }; diff --git a/testsuite/tests/ghci/scripts/ListTuplePunsPpr.script b/testsuite/tests/ghci/scripts/ListTuplePunsPpr.script index 641602ca6427..0e871880900e 100644 --- a/testsuite/tests/ghci/scripts/ListTuplePunsPpr.script +++ b/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# diff --git a/testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout b/testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout index e6c6f8ee5d4b..0c5d4a172a6f 100644 --- a/testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout +++ b/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 diff --git a/testsuite/tests/interface-stability/ghc-experimental-exports.stdout b/testsuite/tests/interface-stability/ghc-experimental-exports.stdout index 973430a43452..1a052cc9a3ca 100644 --- a/testsuite/tests/interface-stability/ghc-experimental-exports.stdout +++ b/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 diff --git a/testsuite/tests/simplStg/should_compile/T15226b.stderr b/testsuite/tests/simplStg/should_compile/T15226b.stderr index f33a3bbef15f..bcd3e73a2fbd 100644 --- a/testsuite/tests/simplStg/should_compile/T15226b.stderr +++ b/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 diff --git a/testsuite/tests/th/TH_tuple1.stdout b/testsuite/tests/th/TH_tuple1.stdout index 21e01437d77a..cf588e49403c 100644 --- a/testsuite/tests/th/TH_tuple1.stdout +++ b/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 -- GitLab