[Git][ghc/ghc][wip/int-index/list-tuple-cleanup] GHC.Base, GHC.Exts: hide MkSolo#

Vladislav Zavialov (@int-index) gitlab at gitlab.haskell.org
Fri Aug 23 10:49:02 UTC 2024



Vladislav Zavialov pushed to branch wip/int-index/list-tuple-cleanup at Glasgow Haskell Compiler / GHC


Commits:
d3d98594 by Vladislav Zavialov at 2024-08-23T13:48:45+03:00
GHC.Base, GHC.Exts: hide MkSolo#

- - - - -


3 changed files:

- libraries/base/src/GHC/Base.hs
- libraries/base/src/GHC/Exts.hs
- testsuite/tests/interface-stability/base-exports.stdout


Changes:

=====================================
libraries/base/src/GHC/Base.hs
=====================================
@@ -152,7 +152,7 @@ import GHC.Internal.IO (seq#)
 import GHC.Internal.Maybe
 import GHC.Types hiding (
   Unit#,
-  Solo#,
+  Solo#(..),
   Tuple0#,
   Tuple1#,
   Tuple2#,


=====================================
libraries/base/src/GHC/Exts.hs
=====================================
@@ -126,7 +126,7 @@ import GHC.Types hiding (
   -- GHC's internal representation of 'TyCon's, for 'Typeable'
   Module, TrName, TyCon, TypeLitSort, KindRep, KindBndr,
   Unit#,
-  Solo#,
+  Solo#(..),
   Tuple0#,
   Tuple1#,
   Tuple2#,


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -3329,7 +3329,6 @@ module GHC.Base where
   data MVar# a b
   type Maybe :: * -> *
   data Maybe a = Nothing | Just a
-  MkSolo# :: forall (k :: RuntimeRep) (a :: TYPE k). a -> (# a #)
   type Module :: *
   data Module = Module TrName TrName
   type Monad :: (* -> *) -> Constraint
@@ -5526,7 +5525,6 @@ module GHC.Exts where
   type role MVar# nominal representational
   type MVar# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType
   data MVar# a b
-  MkSolo# :: forall (k :: RuntimeRep) (a :: TYPE k). a -> (# a #)
   type MultMul :: Multiplicity -> Multiplicity -> Multiplicity
   type family MultMul a b where
     forall (x :: Multiplicity). MultMul One x = x



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d3d98594fefe68c3f802522caf1aeaf23a0a9066
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/20240823/81bfb9e4/attachment-0001.html>


More information about the ghc-commits mailing list