Skip to content

Commit 8140056

Browse files
Make some FFI argument passing changes/doc changes
1 parent 02c706e commit 8140056

File tree

4 files changed

+27
-21
lines changed

4 files changed

+27
-21
lines changed

core/src/Streamly/Internal/Data/MutArray/Type.hs

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -438,10 +438,10 @@ import Prelude hiding
438438
-------------------------------------------------------------------------------
439439

440440
-- NOTE: Have to be "ccall unsafe" so that we can pass unpinned memory to these
441-
-- NOTE: cannot pass Ptr, have to pass MutableByteArray# for safe unpinned
442-
-- memory access in C code.
441+
-- NOTE: for passing unpinned memory safely we have to pass unlifted pointers
442+
-- in FFI so that GC cannot change the wrapper during the call setup.
443443
foreign import ccall unsafe "string.h memcpy" c_memcpy
444-
:: MutableByteArray# RealWorld -> Ptr Word8 -> CSize -> IO (Ptr Word8)
444+
:: MutableByteArray# RealWorld -> Addr# -> CSize -> IO (Ptr Word8)
445445

446446
-- XXX We can pass an Addr# to memchr instead of writing a C wrapper.
447447
foreign import ccall unsafe "memchr_index" c_memchr_index
@@ -2592,13 +2592,13 @@ fromPureStream xs =
25922592
--
25932593
-- /Unsafe:/
25942594
--
2595-
-- 1. The memory pointed by @addr@ must be pinned or static.
2595+
-- 1. The caller has to make sure the pointer is live during the call.
25962596
-- 2. The caller is responsible to ensure that the pointer passed is valid up
25972597
-- to the given length.
25982598
--
25992599
{-# INLINABLE fromPtrN #-}
26002600
fromPtrN :: MonadIO m => Int -> Ptr Word8 -> m (MutArray Word8)
2601-
fromPtrN len addr = do
2601+
fromPtrN len (Ptr addr) = do
26022602
-- memcpy is better than stream copy when the size is known.
26032603
-- XXX We can implement a stream copy in a similar way by streaming Word64
26042604
-- first and then remaining Word8.
@@ -2607,12 +2607,12 @@ fromPtrN len addr = do
26072607
_ <- liftIO $ c_memcpy mbarr addr (fromIntegral len)
26082608
pure (arr { arrEnd = len })
26092609

2610-
-- | @fromW16CString# addr@ copies a C string consisting of bytes and
2610+
-- | @fromCString# addr@ copies a C string consisting of bytes and
26112611
-- terminated by a null byte, into a Word8 array. The null byte is not copied.
26122612
--
26132613
-- /Unsafe:/
26142614
--
2615-
-- 1. The memory pointed by @addr@ must be pinned or static.
2615+
-- 1. The caller has to make sure that the @addr@ is alive during the call.
26162616
-- 2. The caller is responsible to ensure that the pointer passed is valid up
26172617
-- to the point where null byte is found.
26182618
--
@@ -2641,7 +2641,7 @@ fromByteStr# = fromCString#
26412641
--
26422642
-- /Unsafe:/
26432643
--
2644-
-- 1. The memory pointed by @addr@ must be pinned or static.
2644+
-- 1. The caller has to make sure that the @addr@ is alive during the call.
26452645
-- 2. The caller is responsible to ensure that the pointer passed is valid up
26462646
-- to the point where null Word16 is found.
26472647
--
@@ -2867,16 +2867,18 @@ unsafeSplice dst src = do
28672867
(arrContents src) startSrc (arrContents dst) endDst srcLen
28682868
return $ dst {arrEnd = endDst + srcLen}
28692869

2870-
-- |
2870+
-- | Append specified number of bytes from a given pointer to the MutArray.
2871+
--
28712872
-- /Unsafe:/
28722873
--
28732874
-- 1. Does not check the length of the MutArray.
2874-
-- 2. The caller is responsible to ensure that the pointer passed is valid up
2875+
-- 2. The caller has to make sure that the pointer is alive during the call
2876+
-- 3. The caller is responsible to ensure that the pointer passed is valid up
28752877
-- to the given length.
28762878
--
28772879
{-# INLINE unsafeAppendPtrN #-}
28782880
unsafeAppendPtrN :: MonadIO m =>
2879-
MutArray a -> Ptr a -> Int -> m (MutArray a)
2881+
MutArray Word8 -> Ptr Word8 -> Int -> m (MutArray Word8)
28802882
unsafeAppendPtrN dst ptr ptrLen = do
28812883
let newEnd = arrEnd dst + ptrLen
28822884
assertM(newEnd <= arrBound dst)
@@ -3094,6 +3096,7 @@ breakOn sep arr@MutArray{..} = liftIO $ do
30943096
-- Need efficient stream based primitives that work on Word64.
30953097
let marr = getMutByteArray# arrContents
30963098
len = fromIntegral (arrEnd - arrStart)
3099+
-- XXX pass Addr# to memchr instead of using a C wrapper over memchr
30973100
sepIndex <- c_memchr_index marr (fromIntegral arrStart) sep len
30983101
let intIndex = fromIntegral sepIndex
30993102
return $

core/src/Streamly/Internal/Data/MutByteArray/Type.hs

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,6 @@ import Data.Word (Word8)
6868
import Debug.Trace (trace)
6969
#endif
7070
import Foreign.C.Types (CSize(..))
71-
import Foreign.Ptr (castPtr)
7271
import GHC.Base (IO(..))
7372
import System.IO.Unsafe (unsafePerformIO)
7473

@@ -287,23 +286,26 @@ unsafePutSlice src srcStartBytes dst dstStartBytes lenBytes = liftIO $ do
287286
, () #)
288287

289288
foreign import ccall unsafe "string.h memcpy" c_memcpy
290-
:: Addr# -> Ptr Word8 -> CSize -> IO (Ptr Word8)
289+
:: Addr# -> Addr# -> CSize -> IO (Ptr Word8)
291290

292291
-- | @unsafePutPtrN srcPtr dst dstOffset len@ copies @len@ bytes from @srcPtr@
293292
-- to dst at @dstOffset@.
294293
--
295-
-- This is unsafe as it does not check the bounds of @dst@ and the user is
296-
-- responsible to pass a valid pointer up to length @len@..
294+
-- /Unsafe/:
295+
--
296+
-- * does not check the bounds of the @dst@ array.
297+
-- * the caller must ensure that @srcPtr@ is alive during the call
298+
-- * the caller must ensure that @srcPtr@ is valid up to length @len@.
297299
--
298300
{-# INLINE unsafePutPtrN #-}
299301
unsafePutPtrN ::
300302
MonadIO m
301-
=> Ptr a
303+
=> Ptr Word8
302304
-> MutByteArray
303305
-> Int
304306
-> Int
305307
-> m ()
306-
unsafePutPtrN srcPtr dst dstOffset len = liftIO $ do
308+
unsafePutPtrN (Ptr srcAddr) dst dstOffset len = liftIO $ do
307309
#ifdef DEBUG
308310
dstLen <- length dst
309311
when (dstLen - dstOffset < len)
@@ -313,7 +315,7 @@ unsafePutPtrN srcPtr dst dstOffset len = liftIO $ do
313315
let !dstAddr# = (byteArrayContents# (unsafeCoerce# (getMutByteArray# dst)))
314316
!(I# dstOff#) = dstOffset
315317
!dstAddr1# = plusAddr# dstAddr# dstOff#
316-
_ <- c_memcpy dstAddr1# (castPtr srcPtr) (fromIntegral len)
318+
_ <- c_memcpy dstAddr1# srcAddr (fromIntegral len)
317319
pure ()
318320

319321
-- | Unsafe as it does not check whether the start offset and length supplied

core/src/Streamly/Internal/FileSystem/Path/Common.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1809,6 +1809,8 @@ mkQ f =
18091809
foreign import ccall unsafe "string.h strlen" c_strlen
18101810
:: Addr# -> IO CSize
18111811

1812+
-- | Append a separator and a CString to the Array.
1813+
--
18121814
{-# INLINE appendCString #-}
18131815
appendCString :: OS -> Array Word8 -> CString -> IO (Array Word8)
18141816
appendCString os a b@(Ptr addrB#) = do

core/src/Streamly/Internal/FileSystem/Posix/ReadDir.hsc

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -128,7 +128,6 @@ isMetaDir :: Ptr CChar -> IO Bool
128128
isMetaDir dname = do
129129
-- XXX Assuming an encoding that maps "." to ".", this is true for
130130
-- UTF8.
131-
-- Load as soon as possible to optimize memory accesses
132131
c1 <- peek dname
133132
c2 :: Word8 <- peekByteOff dname 1
134133
if (c1 /= fromIntegral (ord '.'))
@@ -152,6 +151,8 @@ lstatDname parent dname = do
152151
if isMeta
153152
then pure (True, True)
154153
else do
154+
-- XXX We can create a pinned array right here since the next call pins
155+
-- it anyway.
155156
path <- appendCString parent dname
156157
Array.asCStringUnsafe (Path.toChunk path) $ \cStr -> do
157158
res <- c_lstat_is_directory cStr
@@ -285,8 +286,6 @@ eitherReader =
285286
{-# INLINE appendCString #-}
286287
appendCString :: PosixPath -> CString -> IO PosixPath
287288
appendCString x@(PosixPath a) b = do
288-
-- XXX Should we ensure that this is pinned in the DT_UNKNOWN case
289-
-- because we always pass it to a C function which pins it anyway.
290289
arr <- PathC.appendCString PathC.Posix a b
291290
pure $ PosixPath arr
292291

0 commit comments

Comments
 (0)