summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorMatthew Craven <5086-clyring@users.noreply.gitlab.haskell.org>2023-02-21 12:59:50 -0500
committerMarge Bot <ben+marge-bot@smart-cactus.org>2023-04-04 01:04:10 -0400
commit9095e297fbb46781fd182210609ce2a3f6c59b7a (patch)
tree98585355e6e01e02465c25d2febfd276adafccfd /libraries
parent220a7a48cabdcfd2ef7bf5dbe3fd6df99e8d3c5b (diff)
downloadhaskell-9095e297fbb46781fd182210609ce2a3f6c59b7a.tar.gz
Add a few more memcpy-ish primops
* copyMutableByteArrayNonOverlapping# * copyAddrToAddr# * copyAddrToAddrNonOverlapping# * setAddrRange# The implementations of copyBytes, moveBytes, and fillBytes in base:Foreign.Marshal.Utils now use these new primops, which can cause us to work a bit harder generating code for them, resulting in the metric increase in T21839c observed by CI on some architectures. But in exchange, we get better code! Metric Increase: T21839c
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Data/Array/Byte.hs4
-rw-r--r--libraries/base/Foreign/Marshal/Utils.hs35
-rw-r--r--libraries/ghc-prim/changelog.md7
3 files changed, 21 insertions, 25 deletions
diff --git a/libraries/base/Data/Array/Byte.hs b/libraries/base/Data/Array/Byte.hs
index 918e20bae8..99a7b0a36e 100644
--- a/libraries/base/Data/Array/Byte.hs
+++ b/libraries/base/Data/Array/Byte.hs
@@ -134,7 +134,7 @@ unsafeCopyByteArray (MutableByteArray dst#) (I# doff#) (ByteArray src#) (I# soff
-- | Copy a slice from one mutable byte array to another
-- or to the same mutable byte array.
--
--- /Note:/ this function does not do bounds checking.
+-- /Note:/ this function does not do bounds or overlap checking.
unsafeCopyMutableByteArray
:: MutableByteArray s -- ^ destination array
-> Int -- ^ offset into destination array
@@ -144,7 +144,7 @@ unsafeCopyMutableByteArray
-> ST s ()
{-# INLINE unsafeCopyMutableByteArray #-}
unsafeCopyMutableByteArray (MutableByteArray dst#) (I# doff#) (MutableByteArray src#) (I# soff#) (I# sz#) =
- ST (\s# -> case copyMutableByteArray# src# soff# dst# doff# sz# s# of
+ ST (\s# -> case copyMutableByteArrayNonOverlapping# src# soff# dst# doff# sz# s# of
s'# -> (# s'#, () #))
-- | @since 4.17.0.0
diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs
index d134788e62..7d6cdcc879 100644
--- a/libraries/base/Foreign/Marshal/Utils.hs
+++ b/libraries/base/Foreign/Marshal/Utils.hs
@@ -1,6 +1,9 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+
-----------------------------------------------------------------------------
-- |
-- Module : Foreign.Marshal.Utils
@@ -50,13 +53,11 @@ module Foreign.Marshal.Utils (
) where
import Data.Maybe
-import Foreign.Ptr ( Ptr, nullPtr )
+import GHC.Ptr ( Ptr(..), nullPtr )
import Foreign.Storable ( Storable(poke) )
-import Foreign.C.Types ( CSize(..), CInt(..) )
import Foreign.Marshal.Alloc ( malloc, alloca )
-import Data.Word ( Word8 )
+import GHC.Word ( Word8(..) )
-import GHC.Real ( fromIntegral )
import GHC.Num
import GHC.Base
@@ -158,9 +159,8 @@ copyBytes
-> Ptr a -- ^ Source
-> Int -- ^ Size in bytes
-> IO ()
-copyBytes dest src size = do
- _ <- memcpy dest src (fromIntegral size)
- return ()
+copyBytes = coerce $ \(Ptr dest#) (Ptr src#) (I# size#) s
+ -> (# copyAddrToAddrNonOverlapping# src# dest# size# s, () #)
-- |Copies the given number of bytes from the second area (source) into the
-- first (destination); the copied areas /may/ overlap
@@ -170,9 +170,8 @@ moveBytes
-> Ptr a -- ^ Source
-> Int -- ^ Size in bytes
-> IO ()
-moveBytes dest src size = do
- _ <- memmove dest src (fromIntegral size)
- return ()
+moveBytes = coerce $ \(Ptr dest#) (Ptr src#) (I# size#) s
+ -> (# copyAddrToAddr# src# dest# size# s, () #)
-- Filling up memory area with required values
-- -------------------------------------------
@@ -180,16 +179,6 @@ moveBytes dest src size = do
-- |Fill a given number of bytes in memory area with a byte value.
--
-- @since 4.8.0.0
-fillBytes :: Ptr a -> Word8 -> Int -> IO ()
-fillBytes dest char size = do
- _ <- memset dest (fromIntegral char) (fromIntegral size)
- return ()
-
--- auxiliary routines
--- -------------------
-
--- |Basic C routines needed for memory copying
---
-foreign import ccall unsafe "string.h" memcpy :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)
-foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)
-foreign import ccall unsafe "string.h" memset :: Ptr a -> CInt -> CSize -> IO (Ptr a)
+fillBytes :: Ptr a -> Word8 -> Int -> IO ()
+fillBytes = coerce $ \(Ptr dest#) (W8# byte#) (I# size#) s
+ -> (# setAddrRange# dest# size# (word2Int# (word8ToWord# byte#)) s, () #)
diff --git a/libraries/ghc-prim/changelog.md b/libraries/ghc-prim/changelog.md
index c78de3c5e2..221325c029 100644
--- a/libraries/ghc-prim/changelog.md
+++ b/libraries/ghc-prim/changelog.md
@@ -14,6 +14,13 @@
- `sameMutVar#`, `sameTVar#`, `sameMVar#`
- `sameIOPort#`, `eqStableName#`.
+- Several new primops were added:
+
+ - `copyMutableByteArrayNonOverlapping#`
+ - `copyAddrToAddr#`
+ - `copyAddrToAddrNonOverlapping#`
+ - `setAddrRange#`
+
## 0.10.0
- Shipped with GHC 9.6.1