[Git][ghc/ghc][wip/no-fptr] 8 commits: base: Introduce GHC.ForeignPtr.Ops module
Ben Gamari
gitlab at gitlab.haskell.org
Mon Nov 30 15:13:01 UTC 2020
Ben Gamari pushed to branch wip/no-fptr at Glasgow Haskell Compiler / GHC
Commits:
a32c5a10 by Ben Gamari at 2020-11-30T10:12:52-05:00
base: Introduce GHC.ForeignPtr.Ops module
This contains a variety of peek/poke operations for ForeignPtr accesses.
- - - - -
38766e93 by Ben Gamari at 2020-11-30T10:12:52-05:00
GHC.IO.Buffer: Use ForeignPtr-specialised peek/poke
- - - - -
24cd42a2 by Ben Gamari at 2020-11-30T10:12:52-05:00
GHC.Data.ByteArray: Initial commit
- - - - -
39cd7b51 by Ben Gamari at 2020-11-30T10:12:52-05:00
GHC.Utils.Binary: Eliminate allocating withForeignPtr uses
- - - - -
4c30f373 by Ben Gamari at 2020-11-30T10:12:52-05:00
base: Eliminate allocating withForeignPtrs from GHC.Event.Array
- - - - -
46b45be9 by Ben Gamari at 2020-11-30T10:12:52-05:00
base: Use unsafeWithForeignPtr in GHC.IO.Buffer
- - - - -
29d2bb26 by Ben Gamari at 2020-11-30T10:12:52-05:00
GHC.Event.Array: Use unsafeWithForeignPtr
- - - - -
10db1230 by Ben Gamari at 2020-11-30T10:12:52-05:00
Bump bytestring submodule
Teach it to use unsafeWithForeignPtr where appropriate.
- - - - -
7 changed files:
- + compiler/GHC/Data/ByteArray.hs
- compiler/GHC/Utils/Binary.hs
- libraries/base/GHC/Event/Array.hs
- + libraries/base/GHC/ForeignPtr/Ops.hs
- libraries/base/GHC/IO/Buffer.hs
- libraries/base/base.cabal
- libraries/bytestring
Changes:
=====================================
compiler/GHC/Data/ByteArray.hs
=====================================
@@ -0,0 +1,280 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE MagicHash #-}
+
+module GHC.Data.ByteArray
+ ( -- * Immutable byte arrays
+ ByteArray
+ , getByteArray
+ , unsafeByteArrayContents
+ , withByteArrayContents
+ , sizeofByteArray
+
+ -- * Mutable byte arrays
+ , MutableByteArray
+ , getMutableByteArray
+ , unsafeMutableByteArrayContents
+ , newMutableByteArray
+ , newPinnedMutableByteArray
+ , copyByteArray
+ , copyAddrToMutableByteArray
+ , unsafeFreezeByteArray
+
+ -- * Writing
+ , writeWordArray
+ , writeWord8Array
+ , writeWord16Array
+ , writeWord32Array
+ , writeWord64Array
+ , writeIntArray
+ , writeInt8Array
+ , writeInt16Array
+ , writeInt32Array
+ , writeInt64Array
+ , writeCharArray
+
+ -- * Reading
+ , readWordArray
+ , readWord8Array
+ , readWord16Array
+ , readWord32Array
+ , readWord64Array
+ , readIntArray
+ , readInt8Array
+ , readInt16Array
+ , readInt32Array
+ , readInt64Array
+ , readCharArray
+
+ -- * Immutable indexing
+ , indexWordArray
+ , indexWord8Array
+ , indexWord16Array
+ , indexWord32Array
+ , indexWord64Array
+ , indexIntArray
+ , indexInt8Array
+ , indexInt16Array
+ , indexInt32Array
+ , indexInt64Array
+ , indexCharArray
+ ) where
+
+import GHC.Base
+import GHC.Exts
+import GHC.Word
+import GHC.Int
+import Unsafe.Coerce
+
+data MutableByteArray = MutableByteArray { getMutableByteArray :: !(MutableByteArray# RealWorld) }
+
+data ByteArray = ByteArray { getByteArray :: !ByteArray# }
+
+unsafeByteArrayContents :: ByteArray -> Ptr a
+unsafeByteArrayContents (ByteArray ba) = Ptr (byteArrayContents# ba)
+
+unsafeMutableByteArrayContents :: MutableByteArray -> Ptr a
+unsafeMutableByteArrayContents = unsafeByteArrayContents . unsafeCoerce
+
+withByteArrayContents :: ByteArray -> (Ptr a -> IO b) -> IO b
+withByteArrayContents (ByteArray ba) f = do
+ r <- f $ Ptr (byteArrayContents# ba)
+ IO $ \s -> case touch# ba s of s' -> (# s', () #)
+ return r
+
+newMutableByteArray :: Int -> IO MutableByteArray
+newMutableByteArray (I# size) = IO $ \s ->
+ case newByteArray# size s of
+ (# s', mba #) -> (# s', MutableByteArray mba #)
+
+newPinnedMutableByteArray :: Int -> IO MutableByteArray
+newPinnedMutableByteArray (I# size) = IO $ \s ->
+ case newPinnedByteArray# size s of
+ (# s', mba #) -> (# s', MutableByteArray mba #)
+
+copyByteArray
+ :: ByteArray -- ^ source
+ -> Int -- ^ source offset
+ -> MutableByteArray -- ^ destination
+ -> Int -- ^ destination offset
+ -> Int -- ^ length to copy
+ -> IO ()
+copyByteArray (ByteArray src) (I# src_ofs) (MutableByteArray dst) (I# dst_ofs) (I# len) =
+ IO $ \s ->
+ case copyByteArray# src src_ofs dst dst_ofs len s of
+ s' -> (# s', () #)
+
+copyAddrToMutableByteArray :: Ptr a -> MutableByteArray -> Int -> Int -> IO ()
+copyAddrToMutableByteArray (Ptr src) (MutableByteArray dst) (I# dst_ofs) (I# len) = IO $ \s ->
+ case copyAddrToByteArray# src dst dst_ofs len s of
+ s' -> (# s', () #)
+
+unsafeFreezeByteArray
+ :: MutableByteArray
+ -> IO ByteArray
+unsafeFreezeByteArray (MutableByteArray mba) = IO $ \s ->
+ case unsafeFreezeByteArray# mba s of
+ (# s', ba #) -> (# s', ByteArray ba #)
+
+sizeofByteArray :: ByteArray -> Int
+sizeofByteArray (ByteArray arr) = I# (sizeofByteArray# arr)
+
+
+readWordArray :: MutableByteArray -> Int -> IO Word
+readWordArray (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readWordArray# arr ix s0 of
+ (# s1, r #) -> (# s1, W# r #)
+
+readWord8Array :: MutableByteArray -> Int -> IO Word8
+readWord8Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readWord8Array# arr ix s0 of
+ (# s1, r #) -> (# s1, W8# r #)
+
+readWord16Array :: MutableByteArray -> Int -> IO Word16
+readWord16Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readWord16Array# arr ix s0 of
+ (# s1, r #) -> (# s1, W16# r #)
+
+readWord32Array :: MutableByteArray -> Int -> IO Word32
+readWord32Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readWord32Array# arr ix s0 of
+ (# s1, r #) -> (# s1, W32# r #)
+
+readWord64Array :: MutableByteArray -> Int -> IO Word64
+readWord64Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readWord64Array# arr ix s0 of
+ (# s1, r #) -> (# s1, W64# r #)
+
+readIntArray :: MutableByteArray -> Int -> IO Int
+readIntArray (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readIntArray# arr ix s0 of
+ (# s1, r #) -> (# s1, I# r #)
+
+readInt8Array :: MutableByteArray -> Int -> IO Int8
+readInt8Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readInt8Array# arr ix s0 of
+ (# s1, r #) -> (# s1, I8# r #)
+
+readInt16Array :: MutableByteArray -> Int -> IO Int16
+readInt16Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readInt16Array# arr ix s0 of
+ (# s1, r #) -> (# s1, I16# r #)
+
+readInt32Array :: MutableByteArray -> Int -> IO Int32
+readInt32Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readInt32Array# arr ix s0 of
+ (# s1, r #) -> (# s1, I32# r #)
+
+readInt64Array :: MutableByteArray -> Int -> IO Int64
+readInt64Array (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readInt64Array# arr ix s0 of
+ (# s1, r #) -> (# s1, I64# r #)
+
+readCharArray :: MutableByteArray -> Int -> IO Char
+readCharArray (MutableByteArray arr) (I# ix) = IO $ \s0 ->
+ case readCharArray# arr ix s0 of
+ (# s1, r #) -> (# s1, C# r #)
+
+
+
+writeWordArray :: MutableByteArray -> Int -> Word -> IO ()
+writeWordArray (MutableByteArray arr) (I# ix) (W# x) = IO $ \s0 ->
+ case writeWordArray# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeWord8Array :: MutableByteArray -> Int -> Word8 -> IO ()
+writeWord8Array (MutableByteArray arr) (I# ix) (W8# x) = IO $ \s0 ->
+ case writeWord8Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeWord16Array :: MutableByteArray -> Int -> Word16 -> IO ()
+writeWord16Array (MutableByteArray arr) (I# ix) (W16# x) = IO $ \s0 ->
+ case writeWord16Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeWord32Array :: MutableByteArray -> Int -> Word32 -> IO ()
+writeWord32Array (MutableByteArray arr) (I# ix) (W32# x) = IO $ \s0 ->
+ case writeWord32Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeWord64Array :: MutableByteArray -> Int -> Word64 -> IO ()
+writeWord64Array (MutableByteArray arr) (I# ix) (W64# x) = IO $ \s0 ->
+ case writeWord64Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeIntArray :: MutableByteArray -> Int -> Int -> IO ()
+writeIntArray (MutableByteArray arr) (I# ix) (I# x) = IO $ \s0 ->
+ case writeIntArray# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeInt8Array :: MutableByteArray -> Int -> Int8 -> IO ()
+writeInt8Array (MutableByteArray arr) (I# ix) (I8# x) = IO $ \s0 ->
+ case writeInt8Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeInt16Array :: MutableByteArray -> Int -> Int16 -> IO ()
+writeInt16Array (MutableByteArray arr) (I# ix) (I16# x) = IO $ \s0 ->
+ case writeInt16Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeInt32Array :: MutableByteArray -> Int -> Int32 -> IO ()
+writeInt32Array (MutableByteArray arr) (I# ix) (I32# x) = IO $ \s0 ->
+ case writeInt32Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeInt64Array :: MutableByteArray -> Int -> Int64 -> IO ()
+writeInt64Array (MutableByteArray arr) (I# ix) (I64# x) = IO $ \s0 ->
+ case writeInt64Array# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+writeCharArray :: MutableByteArray -> Int -> Char -> IO ()
+writeCharArray (MutableByteArray arr) (I# ix) (C# x) = IO $ \s0 ->
+ case writeCharArray# arr ix x s0 of
+ s1 -> (# s1, () #)
+
+
+
+indexWordArray :: ByteArray -> Int -> Word
+indexWordArray (ByteArray arr) (I# ix) =
+ W# (indexWordArray# arr ix)
+
+indexWord8Array :: ByteArray -> Int -> Word8
+indexWord8Array (ByteArray arr) (I# ix) =
+ W8# (indexWord8Array# arr ix)
+
+indexWord16Array :: ByteArray -> Int -> Word16
+indexWord16Array (ByteArray arr) (I# ix) =
+ W16# (indexWord16Array# arr ix)
+
+indexWord32Array :: ByteArray -> Int -> Word32
+indexWord32Array (ByteArray arr) (I# ix) =
+ W32# (indexWord32Array# arr ix)
+
+indexWord64Array :: ByteArray -> Int -> Word64
+indexWord64Array (ByteArray arr) (I# ix) =
+ W64# (indexWord64Array# arr ix)
+
+indexIntArray :: ByteArray -> Int -> Int
+indexIntArray (ByteArray arr) (I# ix) =
+ I# (indexIntArray# arr ix)
+
+indexInt8Array :: ByteArray -> Int -> Int8
+indexInt8Array (ByteArray arr) (I# ix) =
+ I8# (indexInt8Array# arr ix)
+
+indexInt16Array :: ByteArray -> Int -> Int16
+indexInt16Array (ByteArray arr) (I# ix) =
+ I16# (indexInt16Array# arr ix)
+
+indexInt32Array :: ByteArray -> Int -> Int32
+indexInt32Array (ByteArray arr) (I# ix) =
+ I32# (indexInt32Array# arr ix)
+
+indexInt64Array :: ByteArray -> Int -> Int64
+indexInt64Array (ByteArray arr) (I# ix) =
+ I64# (indexInt64Array# arr ix)
+
+indexCharArray :: ByteArray -> Int -> Char
+indexCharArray (ByteArray arr) (I# ix) =
+ C# (indexCharArray# arr ix)
+
=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -6,6 +6,7 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
-- We always optimise this, otherwise performance of a non-optimised
@@ -84,6 +85,7 @@ import Data.Array
import Data.ByteString (ByteString)
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Unsafe as BS
+import GHC.ForeignPtr
import Data.IORef
import Data.Char ( ord, chr )
import Data.Time
@@ -96,7 +98,10 @@ import GHC.Real ( Ratio(..) )
type BinArray = ForeignPtr Word8
-
+#if !MIN_VERSION_base(4,15,0)
+unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
+unsafeWithForeignPtr = withForeignPtr
+#endif
---------------------------------------------------------------
-- BinData
@@ -111,14 +116,14 @@ instance Binary BinData where
put_ bh (BinData sz dat) = do
put_ bh sz
putPrim bh sz $ \dest ->
- withForeignPtr dat $ \orig ->
+ unsafeWithForeignPtr dat $ \orig ->
copyBytes dest orig sz
--
get bh = do
sz <- get bh
dat <- mallocForeignPtrBytes sz
getPrim bh sz $ \orig ->
- withForeignPtr dat $ \dest ->
+ unsafeWithForeignPtr dat $ \dest ->
copyBytes dest orig sz
return (BinData sz dat)
@@ -226,7 +231,7 @@ writeBinMem (BinMem _ ix_r _ arr_r) fn = do
h <- openBinaryFile fn WriteMode
arr <- readIORef arr_r
ix <- readFastMutInt ix_r
- withForeignPtr arr $ \p -> hPutBuf h p ix
+ unsafeWithForeignPtr arr $ \p -> hPutBuf h p ix
hClose h
readBinMem :: FilePath -> IO BinHandle
@@ -236,7 +241,7 @@ readBinMem filename = do
filesize' <- hFileSize h
let filesize = fromIntegral filesize'
arr <- mallocForeignPtrBytes filesize
- count <- withForeignPtr arr $ \p -> hGetBuf h p filesize
+ count <- unsafeWithForeignPtr arr $ \p -> hGetBuf h p filesize
when (count /= filesize) $
error ("Binary.readBinMem: only read " ++ show count ++ " bytes")
hClose h
@@ -280,7 +285,7 @@ putPrim h@(BinMem _ ix_r sz_r arr_r) size f = do
when (ix + size > sz) $
expandBin h (ix + size)
arr <- readIORef arr_r
- withForeignPtr arr $ \op -> f (op `plusPtr` ix)
+ unsafeWithForeignPtr arr $ \op -> f (op `plusPtr` ix)
writeFastMutInt ix_r (ix + size)
-- -- | Similar to putPrim but advances the index by the actual number of
@@ -302,7 +307,10 @@ getPrim (BinMem _ ix_r sz_r arr_r) size f = do
when (ix + size > sz) $
ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing)
arr <- readIORef arr_r
- w <- withForeignPtr arr $ \op -> f (op `plusPtr` ix)
+ w <- f (unsafeForeignPtrToPtr arr `plusPtr` ix)
+ touchForeignPtr arr
+ -- This is safe WRT #17760 as we we guarantee that the above line doesn't
+ -- diverge
writeFastMutInt ix_r (ix + size)
return w
=====================================
libraries/base/GHC/Event/Array.hs
=====================================
@@ -33,7 +33,7 @@ import Foreign.ForeignPtr (ForeignPtr, withForeignPtr)
import Foreign.Ptr (Ptr, nullPtr, plusPtr)
import Foreign.Storable (Storable(..))
import GHC.Base hiding (empty)
-import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_)
+import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_, unsafeWithForeignPtr)
import GHC.Num (Num(..))
import GHC.Real (fromIntegral)
import GHC.Show (show)
@@ -78,9 +78,9 @@ reallocArray p newSize oldSize = reallocHack undefined p
reallocHack dummy src = do
let size = sizeOf dummy
dst <- mallocPlainForeignPtrBytes (newSize * size)
- withForeignPtr src $ \s ->
+ unsafeWithForeignPtr src $ \s ->
when (s /= nullPtr && oldSize > 0) .
- withForeignPtr dst $ \d -> do
+ unsafeWithForeignPtr dst $ \d -> do
_ <- memcpy d s (fromIntegral (oldSize * size))
return ()
return dst
@@ -99,8 +99,8 @@ duplicate a = dupHack undefined a
dupHack dummy (Array ref) = do
AC es len cap <- readIORef ref
ary <- allocArray cap
- withForeignPtr ary $ \dest ->
- withForeignPtr es $ \src -> do
+ unsafeWithForeignPtr ary $ \dest ->
+ unsafeWithForeignPtr es $ \src -> do
_ <- memcpy dest src (fromIntegral (len * sizeOf dummy))
return ()
Array `fmap` newIORef (AC ary len cap)
@@ -119,8 +119,8 @@ unsafeRead :: Storable a => Array a -> Int -> IO a
unsafeRead (Array ref) ix = do
AC es _ cap <- readIORef ref
CHECK_BOUNDS("unsafeRead",cap,ix)
- withForeignPtr es $ \p ->
- peekElemOff p ix
+ unsafeWithForeignPtr es $ \ptr -> peekElemOff ptr ix
+ -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge
unsafeWrite :: Storable a => Array a -> Int -> a -> IO ()
unsafeWrite (Array ref) ix a = do
@@ -130,13 +130,15 @@ unsafeWrite (Array ref) ix a = do
unsafeWrite' :: Storable a => AC a -> Int -> a -> IO ()
unsafeWrite' (AC es _ cap) ix a =
CHECK_BOUNDS("unsafeWrite'",cap,ix)
- withForeignPtr es $ \p ->
- pokeElemOff p ix a
+ unsafeWithForeignPtr es $ \ptr -> pokeElemOff ptr ix a
+ -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge
+-- | Precondition: continuation must not diverge due to use of
+-- 'unsafeWithForeignPtr'.
unsafeLoad :: Array a -> (Ptr a -> Int -> IO Int) -> IO Int
unsafeLoad (Array ref) load = do
AC es _ cap <- readIORef ref
- len' <- withForeignPtr es $ \p -> load p cap
+ len' <- unsafeWithForeignPtr es $ \p -> load p cap
writeIORef ref (AC es len' cap)
return len'
@@ -146,7 +148,7 @@ unsafeCopyFromBuffer :: Storable a => Array a -> Ptr a -> Int -> IO ()
unsafeCopyFromBuffer (Array ref) sptr n =
readIORef ref >>= \(AC es _ cap) ->
CHECK_BOUNDS("unsafeCopyFromBuffer", cap, n)
- withForeignPtr es $ \pdest -> do
+ unsafeWithForeignPtr es $ \pdest -> do
let size = sizeOfPtr sptr undefined
_ <- memcpy pdest sptr (fromIntegral $ n * size)
writeIORef ref (AC es n cap)
@@ -198,7 +200,7 @@ forM_ ary g = forHack ary g undefined
AC es len _ <- readIORef ref
let size = sizeOf dummy
offset = len * size
- withForeignPtr es $ \p -> do
+ unsafeWithForeignPtr es $ \p -> do
let go n | n >= offset = return ()
| otherwise = do
f =<< peek (p `plusPtr` n)
@@ -269,8 +271,8 @@ copy' d dstart s sstart maxCount = copyHack d s undefined
then return dac
else do
AC dst dlen dcap <- ensureCapacity' dac (dstart + count)
- withForeignPtr dst $ \dptr ->
- withForeignPtr src $ \sptr -> do
+ unsafeWithForeignPtr dst $ \dptr ->
+ unsafeWithForeignPtr src $ \sptr -> do
_ <- memcpy (dptr `plusPtr` (dstart * size))
(sptr `plusPtr` (sstart * size))
(fromIntegral (count * size))
@@ -286,7 +288,7 @@ removeAt a i = removeHack a undefined
let size = sizeOf dummy
newLen = oldLen - 1
when (newLen > 0 && i < newLen) .
- withForeignPtr fp $ \ptr -> do
+ unsafeWithForeignPtr fp $ \ptr -> do
_ <- memmove (ptr `plusPtr` (size * i))
(ptr `plusPtr` (size * (i+1)))
(fromIntegral (size * (newLen-i)))
=====================================
libraries/base/GHC/ForeignPtr/Ops.hs
=====================================
@@ -0,0 +1,171 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE Unsafe #-}
+
+{-# OPTIONS_HADDOCK not-home #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.ForeignPtr.Ops
+-- Copyright : (c) The University of Glasgow, 1992-2003
+-- License : see libraries/base/LICENSE
+--
+-- Maintainer : cvs-ghc at haskell.org
+-- Stability : internal
+-- Portability : non-portable (GHC extensions)
+--
+-- GHC's implementation of the 'ForeignPtr' data type.
+--
+-----------------------------------------------------------------------------
+
+module GHC.ForeignPtr.Ops
+ ( -- * Reading
+ peekWord8ForeignPtr
+ , peekWord16ForeignPtr
+ , peekWord32ForeignPtr
+ , peekWord64ForeignPtr
+ , peekWordForeignPtr
+ , peekInt8ForeignPtr
+ , peekInt16ForeignPtr
+ , peekInt32ForeignPtr
+ , peekInt64ForeignPtr
+ , peekIntForeignPtr
+ , peekCharForeignPtr
+ -- * Writing
+ , pokeWord8ForeignPtr
+ , pokeWord16ForeignPtr
+ , pokeWord32ForeignPtr
+ , pokeWord64ForeignPtr
+ , pokeWordForeignPtr
+ , pokeInt8ForeignPtr
+ , pokeInt16ForeignPtr
+ , pokeInt32ForeignPtr
+ , pokeInt64ForeignPtr
+ , pokeIntForeignPtr
+ , pokeCharForeignPtr
+ ) where
+
+import GHC.Word
+import GHC.Int
+import GHC.Base
+import GHC.ForeignPtr
+import GHC.Ptr
+
+withFP :: ForeignPtr a
+ -> (Addr# -> State# RealWorld -> (# State# RealWorld, b #))
+ -> IO b
+withFP fp f =
+ withForeignPtr fp (\(Ptr addr) -> IO (f addr))
+
+peekWord8ForeignPtr :: ForeignPtr ty -> Int -> IO Word8
+peekWord8ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readWord8OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, W8# r #)
+
+peekWord16ForeignPtr :: ForeignPtr ty -> Int -> IO Word16
+peekWord16ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readWord16OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, W16# r #)
+
+peekWord32ForeignPtr :: ForeignPtr ty -> Int -> IO Word32
+peekWord32ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readWord32OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, W32# r #)
+
+peekWord64ForeignPtr :: ForeignPtr ty -> Int -> IO Word64
+peekWord64ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readWord64OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, W64# r #)
+
+peekWordForeignPtr :: ForeignPtr ty -> Int -> IO Word
+peekWordForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readWordOffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, W# r #)
+
+peekInt8ForeignPtr :: ForeignPtr ty -> Int -> IO Int8
+peekInt8ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readInt8OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, I8# r #)
+
+peekInt16ForeignPtr :: ForeignPtr ty -> Int -> IO Int16
+peekInt16ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readInt16OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, I16# r #)
+
+peekInt32ForeignPtr :: ForeignPtr ty -> Int -> IO Int32
+peekInt32ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readInt32OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, I32# r #)
+
+peekInt64ForeignPtr :: ForeignPtr ty -> Int -> IO Int64
+peekInt64ForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readInt64OffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, I64# r #)
+
+peekIntForeignPtr :: ForeignPtr ty -> Int -> IO Int
+peekIntForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readIntOffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, I# r #)
+
+peekCharForeignPtr :: ForeignPtr ty -> Int -> IO Char
+peekCharForeignPtr fp (I# d) = withFP fp $ \addr s0 ->
+ case readCharOffAddr# addr d s0 of
+ (# s1, r #) -> (# s1, C# r #)
+
+pokeWord8ForeignPtr :: ForeignPtr ty -> Int -> Word8 -> IO ()
+pokeWord8ForeignPtr fp (I# d) (W8# n) = withFP fp $ \addr s0 ->
+ case writeWord8OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeWord16ForeignPtr :: ForeignPtr ty -> Int -> Word16 -> IO ()
+pokeWord16ForeignPtr fp (I# d) (W16# n) = withFP fp $ \addr s0 ->
+ case writeWord16OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeWord32ForeignPtr :: ForeignPtr ty -> Int -> Word32 -> IO ()
+pokeWord32ForeignPtr fp (I# d) (W32# n) = withFP fp $ \addr s0 ->
+ case writeWord32OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeWord64ForeignPtr :: ForeignPtr ty -> Int -> Word64 -> IO ()
+pokeWord64ForeignPtr fp (I# d) (W64# n) = withFP fp $ \addr s0 ->
+ case writeWord64OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeWordForeignPtr :: ForeignPtr ty -> Int -> Word -> IO ()
+pokeWordForeignPtr fp (I# d) (W# n) = withFP fp $ \addr s0 ->
+ case writeWord64OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeInt8ForeignPtr :: ForeignPtr ty -> Int -> Int8 -> IO ()
+pokeInt8ForeignPtr fp (I# d) (I8# n) = withFP fp $ \addr s0 ->
+ case writeInt8OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeInt16ForeignPtr :: ForeignPtr ty -> Int -> Int16 -> IO ()
+pokeInt16ForeignPtr fp (I# d) (I16# n) = withFP fp $ \addr s0 ->
+ case writeInt16OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeInt32ForeignPtr :: ForeignPtr ty -> Int -> Int32 -> IO ()
+pokeInt32ForeignPtr fp (I# d) (I32# n) = withFP fp $ \addr s0 ->
+ case writeInt32OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeInt64ForeignPtr :: ForeignPtr ty -> Int -> Int64 -> IO ()
+pokeInt64ForeignPtr fp (I# d) (I64# n) = withFP fp $ \addr s0 ->
+ case writeInt64OffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeIntForeignPtr :: ForeignPtr ty -> Int -> Int -> IO ()
+pokeIntForeignPtr fp (I# d) (I# n) = withFP fp $ \addr s0 ->
+ case writeIntOffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
+pokeCharForeignPtr :: ForeignPtr ty -> Int -> Char -> IO ()
+pokeCharForeignPtr fp (I# d) (C# n) = withFP fp $ \addr s0 ->
+ case writeCharOffAddr# addr d n s0 of
+ s1 -> (# s1, () #)
+
=====================================
libraries/base/GHC/IO/Buffer.hs
=====================================
@@ -72,6 +72,8 @@ import GHC.Word
import GHC.Show
import GHC.Real
import GHC.List
+import GHC.ForeignPtr.Ops
+import GHC.ForeignPtr (unsafeWithForeignPtr)
import Foreign.C.Types
import Foreign.ForeignPtr
import Foreign.Storable
@@ -103,10 +105,10 @@ import Foreign.Storable
type RawBuffer e = ForeignPtr e
readWord8Buf :: RawBuffer Word8 -> Int -> IO Word8
-readWord8Buf arr ix = withForeignPtr arr $ \p -> peekByteOff p ix
+readWord8Buf p ix = peekWord8ForeignPtr p ix
writeWord8Buf :: RawBuffer Word8 -> Int -> Word8 -> IO ()
-writeWord8Buf arr ix w = withForeignPtr arr $ \p -> pokeByteOff p ix w
+writeWord8Buf p ix w = pokeWord8ForeignPtr p ix w
#if defined(CHARBUF_UTF16)
type CharBufElem = Word16
@@ -117,17 +119,17 @@ type CharBufElem = Char
type RawCharBuffer = RawBuffer CharBufElem
peekCharBuf :: RawCharBuffer -> Int -> IO Char
-peekCharBuf arr ix = withForeignPtr arr $ \p -> do
+peekCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> do
(c,_) <- readCharBufPtr p ix
return c
{-# INLINE readCharBuf #-}
readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int)
-readCharBuf arr ix = withForeignPtr arr $ \p -> readCharBufPtr p ix
+readCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> readCharBufPtr p ix
{-# INLINE writeCharBuf #-}
writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int
-writeCharBuf arr ix c = withForeignPtr arr $ \p -> writeCharBufPtr p ix c
+writeCharBuf arr ix c = unsafeWithForeignPtr arr $ \p -> writeCharBufPtr p ix c
{-# INLINE readCharBufPtr #-}
readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int)
=====================================
libraries/base/base.cabal
=====================================
@@ -214,6 +214,7 @@ Library
GHC.Float.RealFracMethods
GHC.Foreign
GHC.ForeignPtr
+ GHC.ForeignPtr.Ops
GHC.GHCi
GHC.GHCi.Helpers
GHC.Generics
=====================================
libraries/bytestring
=====================================
@@ -1 +1 @@
-Subproject commit 8b5d8d0da24aefdc4d950174bf396b32335d7e0f
+Subproject commit 36c2df1feaf10fde8d5848ac47b98d6d62c4e1d7
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d8222cfd23767712c9d4e26f84725d94ceee789c...10db1230433d5e8bfac970868849028d8935957f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d8222cfd23767712c9d4e26f84725d94ceee789c...10db1230433d5e8bfac970868849028d8935957f
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/20201130/8be3005e/attachment-0001.html>
More information about the ghc-commits
mailing list