{-# LANGUAGE CPP #-} module PtrPoker.IO.ByteString where import Data.ByteString.Internal import PtrPoker.Prelude #if MIN_VERSION_bytestring(0,11,0) {-# INLINE pokeByteString #-} pokeByteString :: Ptr Word8 -> ByteString -> IO (Ptr Word8) pokeByteString ptr (BS fptr length) = {-# SCC "pokeByteString" #-} withForeignPtr fptr $ \ bytesPtr -> memcpy ptr bytesPtr length $> plusPtr ptr length #else {-# INLINE pokeByteString #-} pokeByteString :: Ptr Word8 -> ByteString -> IO (Ptr Word8) pokeByteString :: Ptr Word8 -> ByteString -> IO (Ptr Word8) pokeByteString Ptr Word8 ptr (PS ForeignPtr Word8 fptr Int offset Int length) = {-# SCC "pokeByteString" #-} ForeignPtr Word8 -> (Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8) forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr Word8 fptr ((Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8)) -> (Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8) forall a b. (a -> b) -> a -> b $ \ Ptr Word8 bytesPtr -> Ptr Word8 -> Ptr Word8 -> Int -> IO () memcpy Ptr Word8 ptr (Ptr Word8 -> Int -> Ptr Word8 forall a b. Ptr a -> Int -> Ptr b plusPtr Ptr Word8 bytesPtr Int offset) Int length IO () -> Ptr Word8 -> IO (Ptr Word8) forall (f :: * -> *) a b. Functor f => f a -> b -> f b $> Ptr Word8 -> Int -> Ptr Word8 forall a b. Ptr a -> Int -> Ptr b plusPtr Ptr Word8 ptr Int length #endif