{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MagicHash #-}
module Data.Prim.Memory.ByteString
(
MByteString(..)
, Builder
, toBuilderBytes
, fromBuilderBytes
, ByteString(..)
, toByteStringBytes
, fromByteStringBytes
, fromLazyByteStringBytes
, withPtrByteString
, withNoHaltPtrByteString
, ShortByteString(..)
, toShortByteStringBytes
, fromShortByteStringBytes
, byteStringConvertError
) where
import Control.Monad.ST
import Data.ByteString.Builder
import Data.ByteString.Internal
import Data.ByteString.Short.Internal
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import Data.Prim
import Foreign.Prim
import Control.Prim.Monad
import GHC.ForeignPtr
import Data.Prim.Memory.Ptr
import Data.Prim.Memory.Bytes.Internal
( Bytes(..)
, Pinned(..)
, allocMBytes
, freezeMBytes
, byteCountBytes
, relaxPinnedBytes
, toForeignPtrBytes
, castForeignPtrToBytes
, byteStringConvertError
)
newtype MByteString s = MByteString ByteString
toByteStringBytes :: Bytes 'Pin -> ByteString
{-# INLINE toByteStringBytes #-}
toByteStringBytes b =
#if MIN_VERSION_bytestring(0,11,0)
BS (toForeignPtrBytes b) (coerce (byteCountBytes b))
#else
PS (toForeignPtrBytes b) 0 (coerce (byteCountBytes b))
#endif
castByteStringBytes :: ByteString -> Either String (Bytes 'Pin)
#if MIN_VERSION_bytestring(0,11,0)
castByteStringBytes (BS fptr n) = do
#else
castByteStringBytes (PS fptr o n) = do
unless (o == 0) sliceError
#endif
b <- castForeignPtrToBytes fptr
unless (unCount (byteCountBytes b) == n) sliceError
Right b
where
sliceError = Left "ByteString was sliced"
{-# INLINE castByteStringBytes #-}
toShortByteStringBytes :: Bytes p -> ShortByteString
toShortByteStringBytes (Bytes ba#) = SBS ba#
{-# INLINE toShortByteStringBytes #-}
fromShortByteStringBytes :: ShortByteString -> Bytes 'Inc
fromShortByteStringBytes (SBS ba#) = Bytes ba#
{-# INLINE fromShortByteStringBytes #-}
toBuilderBytes :: Bytes p -> Builder
toBuilderBytes = shortByteString . toShortByteStringBytes
{-# INLINE[1] toBuilderBytes #-}
{-# RULES
"toBuilderBytes" toBuilderBytes = byteString . toByteStringBytes
#-}
fromBuilderBytes :: Builder -> Bytes 'Pin
fromBuilderBytes b = fromLazyByteStringBytes (toLazyByteString b)
{-# INLINE fromBuilderBytes #-}
fromLazyByteStringBytes :: BSL.ByteString -> Bytes 'Pin
fromLazyByteStringBytes = fromByteStringBytes . BSL.toStrict
{-# INLINE fromLazyByteStringBytes #-}
fromByteStringBytes :: Typeable p => ByteString -> Bytes p
fromByteStringBytes bs =
case castByteStringBytes bs of
Right b -> relaxPinnedBytes b
Left _ ->
runST $
withPtrByteString bs $ \ptr -> do
let c = Count (BS.length bs) :: Count Word8
mb <- allocMBytes c
copyPtrToMBytes ptr 0 mb 0 c
freezeMBytes mb
{-# INLINE fromByteStringBytes #-}
withPtrByteString :: MonadPrim s m => ByteString -> (Ptr a -> m b) -> m b
#if MIN_VERSION_bytestring(0,11,0)
withPtrByteString (BS (ForeignPtr addr# ptrContents) _) f = do
#else
withPtrByteString (PS (ForeignPtr addr'# ptrContents) (I# o#) _) f = do
let addr# = addr'# `plusAddr#` o#
#endif
r <- f (Ptr addr#)
r <$ touch ptrContents
{-# INLINE withPtrByteString #-}
withNoHaltPtrByteString :: MonadUnliftPrim s m => ByteString -> (Ptr a -> m b) -> m b
#if MIN_VERSION_bytestring(0,11,0)
withNoHaltPtrByteString (BS (ForeignPtr addr# ptrContents) _) f = do
#else
withNoHaltPtrByteString (PS (ForeignPtr addr'# ptrContents) (I# o#) _) f = do
let addr# = addr'# `plusAddr#` o#
#endif
withAliveUnliftPrim ptrContents $ f (Ptr addr#)
{-# INLINE withNoHaltPtrByteString #-}