{-# language CPP #-}
module Graphics.Vulkan.CStruct.Utils ( pokeFixedLengthByteString
, pokeFixedLengthNullTerminatedByteString
, peekByteStringFromSizedVectorPtr
, lowerArrayPtr
, advancePtrBytes
, FixedArray
) where
import Foreign.Marshal.Array (allocaArray)
import Foreign.Marshal.Utils (copyBytes)
import Foreign.Storable (peekElemOff)
import Foreign.Storable (pokeElemOff)
import GHC.Ptr (castPtr)
import Foreign.Ptr (plusPtr)
import GHC.TypeNats (natVal)
import qualified Data.ByteString (length)
import Data.ByteString (packCString)
import Data.ByteString (packCStringLen)
import Data.ByteString (take)
import Data.ByteString (unpack)
import Data.ByteString.Unsafe (unsafeUseAsCString)
import Data.Vector (ifoldr)
import qualified Data.Vector (length)
import qualified Data.Vector.Generic ((++))
import qualified Data.Vector.Generic (empty)
import qualified Data.Vector.Generic (fromList)
import qualified Data.Vector.Generic (length)
import qualified Data.Vector.Generic (replicate)
import qualified Data.Vector.Generic (snoc)
import qualified Data.Vector.Generic (take)
import Data.Proxy (Proxy(..))
import Foreign.C.Types (CChar(..))
import Foreign.Storable (Storable)
import Foreign.Ptr (Ptr)
import GHC.TypeNats (type(<=))
import GHC.TypeNats (KnownNat)
import Data.Word (Word8)
import Data.ByteString (ByteString)
import GHC.TypeNats (Nat)
import Data.Kind (Type)
import Data.Vector (Vector)
import qualified Data.Vector.Generic (Vector)
data FixedArray (n :: Nat) (a :: Type)
pokeFixedLengthNullTerminatedByteString
:: forall n
. KnownNat n
=> Ptr (FixedArray n CChar)
-> ByteString
-> IO ()
pokeFixedLengthNullTerminatedByteString to bs =
unsafeUseAsCString bs $ \from -> do
let maxLength = fromIntegral (natVal (Proxy @n))
len = min maxLength (Data.ByteString.length bs)
end = min (maxLength - 1) len
copyBytes (lowerArrayPtr to) from len
pokeElemOff (lowerArrayPtr to) end 0
pokeFixedLengthByteString
:: forall n
. KnownNat n
=> Ptr (FixedArray n Word8)
-> ByteString
-> IO ()
pokeFixedLengthByteString to bs = unsafeUseAsCString bs $ \from -> do
let maxLength = fromIntegral (natVal (Proxy @n))
len = min maxLength (Data.ByteString.length bs)
copyBytes (lowerArrayPtr to) (castPtr @CChar @Word8 from) len
peekByteStringFromSizedVectorPtr
:: forall n
. KnownNat n
=> Ptr (FixedArray n Word8)
-> IO ByteString
peekByteStringFromSizedVectorPtr p = packCStringLen (castPtr p, fromIntegral (natVal (Proxy @n)))
lowerArrayPtr
:: forall a n
. Ptr (FixedArray n a)
-> Ptr a
lowerArrayPtr = castPtr
advancePtrBytes :: Ptr a -> Int -> Ptr a
advancePtrBytes = plusPtr