[Git][ghc/ghc][master] ghc-prim: levity-polymorphic array equality ops

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Feb 21 23:36:55 UTC 2023



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


Commits:
f70a0239 by sheaf at 2023-02-21T18:36:35-05:00
ghc-prim: levity-polymorphic array equality ops

This patch changes the pointer-equality comparison operations in
GHC.Prim.PtrEq to work with arrays of unlifted values, e.g.

  sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int#

Fixes #22976

- - - - -


3 changed files:

- docs/users_guide/9.8.1-notes.rst
- libraries/ghc-prim/GHC/Prim/PtrEq.hs
- libraries/ghc-prim/changelog.md


Changes:

=====================================
docs/users_guide/9.8.1-notes.rst
=====================================
@@ -44,6 +44,17 @@ Runtime system
 ``ghc-prim`` library
 ~~~~~~~~~~~~~~~~~~~~
 
+- Primitive pointer comparison functions are now levity-polymorphic, e.g. ::
+
+      sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int#
+
+  This change affects the following functions:
+
+    - ``sameArray#``, ``sameMutableArray#``,
+    - ``sameSmallArray#``, ``sameSmallMutableArray#``,
+    - ``sameMutVar#``, ``sameTVar#``, ``sameMVar#``
+    - ``sameIOPort#``, ``eqStableName#``.
+
 ``ghc`` library
 ~~~~~~~~~~~~~~~
 


=====================================
libraries/ghc-prim/GHC/Prim/PtrEq.hs
=====================================
@@ -3,6 +3,8 @@
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -38,7 +40,8 @@ module GHC.Prim.PtrEq
   ) where
 
 import GHC.Prim
-import GHC.Types (UnliftedType) -- Also make implicit dependency known to build system
+import GHC.Types -- Also make implicit dependency known to build system
+  ( RuntimeRep(BoxedRep), UnliftedType )
 default () -- Double and Integer aren't available yet
 
 {- **********************************************************************
@@ -91,19 +94,19 @@ unsafePtrEquality# = reallyUnsafePtrEquality#
 --   in primops.txt.pp
 
 -- | Compare the underlying pointers of two arrays.
-sameArray# :: Array# a -> Array# a -> Int#
+sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int#
 sameArray# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two mutable arrays.
-sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Int#
+sameMutableArray# :: forall {l} s (a :: TYPE (BoxedRep l)). MutableArray# s a -> MutableArray# s a -> Int#
 sameMutableArray# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two small arrays.
-sameSmallArray# :: SmallArray# a -> SmallArray# a -> Int#
+sameSmallArray# :: forall {l} (a :: TYPE (BoxedRep l)). SmallArray# a -> SmallArray# a -> Int#
 sameSmallArray# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two small mutable arrays.
-sameSmallMutableArray# :: SmallMutableArray# s a -> SmallMutableArray# s a -> Int#
+sameSmallMutableArray# :: forall {l} s (a :: TYPE (BoxedRep l)). SmallMutableArray# s a -> SmallMutableArray# s a -> Int#
 sameSmallMutableArray# = unsafePtrEquality#
 
 -- | Compare the pointers of two byte arrays.
@@ -115,23 +118,23 @@ sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int#
 sameMutableByteArray# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two 'MutVar#'s.
-sameMutVar# :: MutVar# s a -> MutVar# s a -> Int#
+sameMutVar# :: forall {l} s (a :: TYPE (BoxedRep l)). MutVar# s a -> MutVar# s a -> Int#
 sameMutVar# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two 'TVar#'s.
-sameTVar# :: TVar# s a -> TVar# s a -> Int#
+sameTVar# :: forall {l} s (a :: TYPE (BoxedRep l)). TVar# s a -> TVar# s a -> Int#
 sameTVar# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two 'MVar#'s.
-sameMVar# :: MVar# s a -> MVar# s a -> Int#
+sameMVar# :: forall {l} s (a :: TYPE (BoxedRep l)). MVar# s a -> MVar# s a -> Int#
 sameMVar# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two 'IOPort#'s.
-sameIOPort# :: IOPort# s a -> IOPort# s a -> Int#
+sameIOPort# :: forall {l} s (a :: TYPE (BoxedRep l)). IOPort# s a -> IOPort# s a -> Int#
 sameIOPort# = unsafePtrEquality#
 
 -- | Compare the underlying pointers of two 'PromptTag#'s.
-samePromptTag# :: PromptTag# a -> PromptTag# a -> Int#
+samePromptTag# :: forall a. PromptTag# a -> PromptTag# a -> Int#
 samePromptTag# = unsafePtrEquality#
 
 -- Note [Comparing stable names]
@@ -145,5 +148,6 @@ samePromptTag# = unsafePtrEquality#
 -- does the trick.
 
 -- | Compare two stable names for equality.
-eqStableName# :: StableName# a -> StableName# b -> Int#
+eqStableName# :: forall {k} {l} (a :: TYPE (BoxedRep k)) (b :: TYPE (BoxedRep l))
+              . StableName# a -> StableName# b -> Int#
 eqStableName# = unsafePtrEquality#


=====================================
libraries/ghc-prim/changelog.md
=====================================
@@ -1,3 +1,19 @@
+## 0.11.0
+
+- Shipped with GHC 9.8.1
+
+- Primitive pointer comparison functions are now levity-polymorphic, e.g.
+
+  ```haskell
+  sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int#
+  ```
+
+  This change affects the following functions:
+    - `sameArray#`, `sameMutableArray#`,
+    - `sameSmallArray#`, `sameSmallMutableArray#`,
+    - `sameMutVar#`, `sameTVar#`, `sameMVar#`
+    - `sameIOPort#`, `eqStableName#`.
+
 ## 0.10.0
 
 - Shipped with GHC 9.6.1



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f70a0239490ebea25e50c61c01f945d8df41e92f
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/20230221/174af4df/attachment-0001.html>


More information about the ghc-commits mailing list