Skip to content

Commit

Permalink
Use plusForeignPtr (Close #174)
Browse files Browse the repository at this point in the history
  • Loading branch information
ekmett committed Jun 5, 2019
1 parent 715094d commit 873d832
Show file tree
Hide file tree
Showing 11 changed files with 265 additions and 217 deletions.
233 changes: 116 additions & 117 deletions Data/ByteString.hs

Large diffs are not rendered by default.

10 changes: 5 additions & 5 deletions Data/ByteString/Builder/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -203,7 +203,7 @@ newBuffer size = do
{-# INLINE byteStringFromBuffer #-}
byteStringFromBuffer :: Buffer -> S.ByteString
byteStringFromBuffer (Buffer fpbuf (BufferRange op _)) =
S.PS fpbuf 0 (op `minusPtr` unsafeForeignPtrToPtr fpbuf)
S.BS fpbuf (op `minusPtr` unsafeForeignPtrToPtr fpbuf)

-- | Prepend the filled part of a 'Buffer' to a lazy 'L.ByteString'
-- trimming it if necessary.
Expand Down Expand Up @@ -857,7 +857,7 @@ byteStringThreshold :: Int -> S.ByteString -> Builder
byteStringThreshold maxCopySize =
\bs -> builder $ step bs
where
step !bs@(S.PS _ _ len) !k br@(BufferRange !op _)
step !bs@(S.BS _ len) !k br@(BufferRange !op _)
| len <= maxCopySize = byteStringCopyStep bs k br
| otherwise = return $ insertChunk op bs k

Expand All @@ -873,7 +873,7 @@ byteStringCopy = \bs -> builder $ byteStringCopyStep bs

{-# INLINE byteStringCopyStep #-}
byteStringCopyStep :: S.ByteString -> BuildStep a -> BuildStep a
byteStringCopyStep (S.PS ifp ioff isize) !k0 br0@(BufferRange op ope)
byteStringCopyStep (S.BS ifp isize) !k0 br0@(BufferRange op ope)
-- Ensure that the common case is not recursive and therefore yields
-- better code.
| op' <= ope = do copyBytes op ip isize
Expand All @@ -882,7 +882,7 @@ byteStringCopyStep (S.PS ifp ioff isize) !k0 br0@(BufferRange op ope)
| otherwise = do wrappedBytesCopyStep (BufferRange ip ipe) k br0
where
op' = op `plusPtr` isize
ip = unsafeForeignPtrToPtr ifp `plusPtr` ioff
ip = unsafeForeignPtrToPtr ifp
ipe = ip `plusPtr` isize
k br = do touchForeignPtr ifp -- input consumed: OK to release here
k0 br
Expand Down Expand Up @@ -1147,7 +1147,7 @@ buildStepToCIOS !(AllocationStrategy nextBuffer bufSize trim) =
-- FIXME: We could reuse the trimmed buffer here.
return $ Yield1 bs (mkCIOS False)
| otherwise =
return $ Yield1 (S.PS fpbuf 0 chunkSize) (mkCIOS False)
return $ Yield1 (S.BS fpbuf chunkSize) (mkCIOS False)
where
chunkSize = op' `minusPtr` pbuf
size = pe `minusPtr` pbuf
6 changes: 3 additions & 3 deletions Data/ByteString/Builder/Prim.hs
Original file line number Diff line number Diff line change
Expand Up @@ -643,10 +643,10 @@ primMapByteStringBounded w =
\bs -> builder $ step bs
where
bound = I.sizeBound w
step (S.PS ifp ioff isize) !k =
goBS (unsafeForeignPtrToPtr ifp `plusPtr` ioff)
step (S.BS ifp isize) !k =
goBS (unsafeForeignPtrToPtr ifp)
where
!ipe = unsafeForeignPtrToPtr ifp `plusPtr` (ioff + isize)
!ipe = unsafeForeignPtrToPtr ifp `plusPtr` isize
goBS !ip0 !br@(BufferRange op0 ope)
| ip0 >= ipe = do
touchForeignPtr ifp -- input buffer consumed
Expand Down
2 changes: 1 addition & 1 deletion Data/ByteString/Builder/Prim/Internal/Base16.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ import Foreign
newtype EncodingTable = EncodingTable (ForeignPtr Word8)

tableFromList :: [Word8] -> EncodingTable
tableFromList xs = case S.pack xs of S.PS fp _ _ -> EncodingTable fp
tableFromList xs = case S.pack xs of S.BS fp _ -> EncodingTable fp

unsafeIndex :: EncodingTable -> Int -> IO Word8
unsafeIndex (EncodingTable table) = peekElemOff (unsafeForeignPtrToPtr table)
Expand Down
16 changes: 8 additions & 8 deletions Data/ByteString/Char8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -791,12 +791,12 @@ unsafeHead = w2c . B.unsafeHead
-- > break isSpace == breakSpace
--
breakSpace :: ByteString -> (ByteString,ByteString)
breakSpace (PS x s l) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> do
i <- firstspace (p `plusPtr` s) 0 l
breakSpace (BS x l) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> do
i <- firstspace p 0 l
return $! case () of {_
| i == 0 -> (empty, PS x s l)
| i == l -> (PS x s l, empty)
| otherwise -> (PS x s i, PS x (s+i) (l-i))
| i == 0 -> (empty, BS x l)
| i == l -> (BS x l, empty)
| otherwise -> (BS x i, BS (plusForeignPtr x i) (l-i))
}
{-# INLINE breakSpace #-}

Expand All @@ -813,9 +813,9 @@ firstspace !ptr !n !m
-- > dropWhile isSpace == dropSpace
--
dropSpace :: ByteString -> ByteString
dropSpace (PS x s l) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> do
i <- firstnonspace (p `plusPtr` s) 0 l
return $! if i == l then empty else PS x (s+i) (l-i)
dropSpace (BS x l) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> do
i <- firstnonspace p 0 l
return $! if i == l then empty else BS (plusForeignPtr x i) (l-i)
{-# INLINE dropSpace #-}

firstnonspace :: Ptr Word8 -> Int -> Int -> IO Int
Expand Down
Loading

0 comments on commit 873d832

Please sign in to comment.