{-# LANGUAGE CPP #-}

module PtrPoker.Compat.ByteString (poke) where

import Data.ByteString.Internal
import Foreign.Marshal.Utils
import qualified PtrPoker.Compat.ForeignPtr as ForeignPtr
import PtrPoker.Prelude hiding (poke)

{-# INLINE poke #-}
poke :: ByteString -> Ptr Word8 -> IO (Ptr Word8)

#if MIN_VERSION_bytestring(0,11,0)

poke :: ByteString -> Ptr Word8 -> IO (Ptr Word8)
poke (BS ForeignPtr Word8
fptr Int
length) Ptr Word8
ptr =
  {-# SCC "poke" #-}
  forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
ForeignPtr.unsafeWithForeignPtr ForeignPtr Word8
fptr forall a b. (a -> b) -> a -> b
$ \ Ptr Word8
bytesPtr ->
    forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Word8
ptr Ptr Word8
bytesPtr Int
length forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$>
    forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
length

#else

poke (PS fptr offset length) ptr =
  {-# SCC "poke" #-}
  ForeignPtr.unsafeWithForeignPtr fptr $ \ bytesPtr ->
    copyBytes ptr (plusPtr bytesPtr offset) length $>
    plusPtr ptr length

#endif