{-# language CPP #-}
module Vulkan.Core10.SparseResourceMemoryManagement ( getImageSparseMemoryRequirements
, getPhysicalDeviceSparseImageFormatProperties
, queueBindSparse
, SparseImageFormatProperties(..)
, SparseImageMemoryRequirements(..)
, SparseMemoryBind(..)
, SparseImageMemoryBind(..)
, SparseBufferMemoryBindInfo(..)
, SparseImageOpaqueMemoryBindInfo(..)
, SparseImageMemoryBindInfo(..)
, BindSparseInfo(..)
) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (Buffer)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkGetImageSparseMemoryRequirements))
import Vulkan.Dynamic (DeviceCmds(pVkQueueBindSparse))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (DeviceGroupBindSparseInfo)
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.BaseType (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.SharedTypes (Extent3D)
import Vulkan.Core10.Handles (Fence)
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.Format (Format(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Image (ImageSubresource)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling(..))
import Vulkan.Core10.Enums.ImageType (ImageType)
import Vulkan.Core10.Enums.ImageType (ImageType(..))
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlagBits(..))
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSparseImageFormatProperties))
import Vulkan.Core10.SharedTypes (Offset3D)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Handles (Queue)
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (Queue_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits(..))
import Vulkan.Core10.Handles (Semaphore)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.SparseImageFormatFlagBits (SparseImageFormatFlags)
import Vulkan.Core10.Enums.SparseMemoryBindFlagBits (SparseMemoryBindFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore (TimelineSemaphoreSubmitInfo)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BIND_SPARSE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetImageSparseMemoryRequirements
:: FunPtr (Ptr Device_T -> Image -> Ptr Word32 -> Ptr SparseImageMemoryRequirements -> IO ()) -> Ptr Device_T -> Image -> Ptr Word32 -> Ptr SparseImageMemoryRequirements -> IO ()
getImageSparseMemoryRequirements :: forall io . MonadIO io => Device -> Image -> io (("sparseMemoryRequirements" ::: Vector SparseImageMemoryRequirements))
getImageSparseMemoryRequirements :: Device
-> Image
-> io
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
getImageSparseMemoryRequirements device :: Device
device image :: Image
image = IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> io
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> io
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> (ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> io
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> io
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> io
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b. (a -> b) -> a -> b
$ do
let vkGetImageSparseMemoryRequirementsPtr :: FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
vkGetImageSparseMemoryRequirementsPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
pVkGetImageSparseMemoryRequirements (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
())
-> IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
vkGetImageSparseMemoryRequirementsPtr FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
-> FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetImageSparseMemoryRequirements is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetImageSparseMemoryRequirements' :: Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ()
vkGetImageSparseMemoryRequirements' = FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
-> Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ()
mkVkGetImageSparseMemoryRequirements FunPtr
(Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
vkGetImageSparseMemoryRequirementsPtr
let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
"pSparseMemoryRequirementCount" ::: Ptr Word32
pPSparseMemoryRequirementCount <- ((("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("pSparseMemoryRequirementCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("pSparseMemoryRequirementCount" ::: Ptr Word32))
-> ((("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("pSparseMemoryRequirementCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> (("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO ())
-> (("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSparseMemoryRequirementCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
())
-> IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ()
vkGetImageSparseMemoryRequirements' Ptr Device_T
device' (Image
image) ("pSparseMemoryRequirementCount" ::: Ptr Word32
pPSparseMemoryRequirementCount) ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
forall a. Ptr a
nullPtr)
Word32
pSparseMemoryRequirementCount <- IO Word32
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
Word32)
-> IO Word32
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSparseMemoryRequirementCount" ::: Ptr Word32
pPSparseMemoryRequirementCount
"pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
pPSparseMemoryRequirements <- ((("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements))
-> ((("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
forall a b. (a -> b) -> a -> b
$ IO
("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> (("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ())
-> (("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO
("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
forall a. Int -> IO (Ptr a)
callocBytes @SparseImageMemoryRequirements ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSparseMemoryRequirementCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48)) ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
())
-> [Int]
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
[()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
())
-> ((()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
pPSparseMemoryRequirements ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int
-> "pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) :: Ptr SparseImageMemoryRequirements) (IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ((()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> (()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ()
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSparseMemoryRequirementCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
())
-> IO ()
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Image
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO ()
vkGetImageSparseMemoryRequirements' Ptr Device_T
device' (Image
image) ("pSparseMemoryRequirementCount" ::: Ptr Word32
pPSparseMemoryRequirementCount) (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
pPSparseMemoryRequirements))
Word32
pSparseMemoryRequirementCount' <- IO Word32
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
Word32)
-> IO Word32
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSparseMemoryRequirementCount" ::: Ptr Word32
pPSparseMemoryRequirementCount
"sparseMemoryRequirements" ::: Vector SparseImageMemoryRequirements
pSparseMemoryRequirements' <- IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO SparseImageMemoryRequirements)
-> IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSparseMemoryRequirementCount')) (\i :: Int
i -> ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO SparseImageMemoryRequirements
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageMemoryRequirements ((("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
pPSparseMemoryRequirements) ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int
-> "pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryRequirements)))
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements))
-> ("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
-> ContT
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
IO
("sparseMemoryRequirements"
::: Vector SparseImageMemoryRequirements)
forall a b. (a -> b) -> a -> b
$ ("sparseMemoryRequirements" ::: Vector SparseImageMemoryRequirements
pSparseMemoryRequirements')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPhysicalDeviceSparseImageFormatProperties
:: FunPtr (Ptr PhysicalDevice_T -> Format -> ImageType -> SampleCountFlagBits -> ImageUsageFlags -> ImageTiling -> Ptr Word32 -> Ptr SparseImageFormatProperties -> IO ()) -> Ptr PhysicalDevice_T -> Format -> ImageType -> SampleCountFlagBits -> ImageUsageFlags -> ImageTiling -> Ptr Word32 -> Ptr SparseImageFormatProperties -> IO ()
getPhysicalDeviceSparseImageFormatProperties :: forall io . MonadIO io => PhysicalDevice -> Format -> ImageType -> ("samples" ::: SampleCountFlagBits) -> ImageUsageFlags -> ImageTiling -> io (("properties" ::: Vector SparseImageFormatProperties))
getPhysicalDeviceSparseImageFormatProperties :: PhysicalDevice
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> io ("properties" ::: Vector SparseImageFormatProperties)
getPhysicalDeviceSparseImageFormatProperties physicalDevice :: PhysicalDevice
physicalDevice format :: Format
format type' :: ImageType
type' samples :: "samples" ::: SampleCountFlagBits
samples usage :: ImageUsageFlags
usage tiling :: ImageTiling
tiling = IO ("properties" ::: Vector SparseImageFormatProperties)
-> io ("properties" ::: Vector SparseImageFormatProperties)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("properties" ::: Vector SparseImageFormatProperties)
-> io ("properties" ::: Vector SparseImageFormatProperties))
-> (ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
-> io ("properties" ::: Vector SparseImageFormatProperties)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
-> io ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
-> io ("properties" ::: Vector SparseImageFormatProperties)
forall a b. (a -> b) -> a -> b
$ do
let vkGetPhysicalDeviceSparseImageFormatPropertiesPtr :: FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
vkGetPhysicalDeviceSparseImageFormatPropertiesPtr = InstanceCmds
-> FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
pVkGetPhysicalDeviceSparseImageFormatProperties (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ())
-> IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
vkGetPhysicalDeviceSparseImageFormatPropertiesPtr FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
-> FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceSparseImageFormatProperties is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPhysicalDeviceSparseImageFormatProperties' :: Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ()
vkGetPhysicalDeviceSparseImageFormatProperties' = FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
-> Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ()
mkVkGetPhysicalDeviceSparseImageFormatProperties FunPtr
(Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ())
vkGetPhysicalDeviceSparseImageFormatPropertiesPtr
let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
"pSparseMemoryRequirementCount" ::: Ptr Word32
pPPropertyCount <- ((("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("pSparseMemoryRequirementCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("pSparseMemoryRequirementCount" ::: Ptr Word32))
-> ((("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("pSparseMemoryRequirementCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> (("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO ())
-> (("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSparseMemoryRequirementCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ())
-> IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ()
vkGetPhysicalDeviceSparseImageFormatProperties' Ptr PhysicalDevice_T
physicalDevice' (Format
format) (ImageType
type') ("samples" ::: SampleCountFlagBits
samples) (ImageUsageFlags
usage) (ImageTiling
tiling) ("pSparseMemoryRequirementCount" ::: Ptr Word32
pPPropertyCount) ("pProperties" ::: Ptr SparseImageFormatProperties
forall a. Ptr a
nullPtr)
Word32
pPropertyCount <- IO Word32
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO Word32)
-> IO Word32
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSparseMemoryRequirementCount" ::: Ptr Word32
pPPropertyCount
"pProperties" ::: Ptr SparseImageFormatProperties
pPProperties <- ((("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("pProperties" ::: Ptr SparseImageFormatProperties)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("pProperties" ::: Ptr SparseImageFormatProperties))
-> ((("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("pProperties" ::: Ptr SparseImageFormatProperties)
forall a b. (a -> b) -> a -> b
$ IO ("pProperties" ::: Ptr SparseImageFormatProperties)
-> (("pProperties" ::: Ptr SparseImageFormatProperties) -> IO ())
-> (("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pProperties" ::: Ptr SparseImageFormatProperties)
forall a. Int -> IO (Ptr a)
callocBytes @SparseImageFormatProperties ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 20)) ("pProperties" ::: Ptr SparseImageFormatProperties) -> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ())
-> [Int]
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO [()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((() -> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ())
-> ((()
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pProperties" ::: Ptr SparseImageFormatProperties
pPProperties ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 20) :: Ptr SparseImageFormatProperties) (IO ("properties" ::: Vector SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> ((()
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties))
-> (() -> IO ("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ("properties" ::: Vector SparseImageFormatProperties))
-> () -> IO ("properties" ::: Vector SparseImageFormatProperties)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ())
-> IO ()
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ("samples" ::: SampleCountFlagBits)
-> ImageUsageFlags
-> ImageTiling
-> ("pSparseMemoryRequirementCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO ()
vkGetPhysicalDeviceSparseImageFormatProperties' Ptr PhysicalDevice_T
physicalDevice' (Format
format) (ImageType
type') ("samples" ::: SampleCountFlagBits
samples) (ImageUsageFlags
usage) (ImageTiling
tiling) ("pSparseMemoryRequirementCount" ::: Ptr Word32
pPPropertyCount) (("pProperties" ::: Ptr SparseImageFormatProperties
pPProperties))
Word32
pPropertyCount' <- IO Word32
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO Word32)
-> IO Word32
-> ContT
("properties" ::: Vector SparseImageFormatProperties) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSparseMemoryRequirementCount" ::: Ptr Word32
pPPropertyCount
"properties" ::: Vector SparseImageFormatProperties
pProperties' <- IO ("properties" ::: Vector SparseImageFormatProperties)
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("properties" ::: Vector SparseImageFormatProperties)
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties))
-> IO ("properties" ::: Vector SparseImageFormatProperties)
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO SparseImageFormatProperties)
-> IO ("properties" ::: Vector SparseImageFormatProperties)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount')) (\i :: Int
i -> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO SparseImageFormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageFormatProperties ((("pProperties" ::: Ptr SparseImageFormatProperties
pPProperties) ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (20 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageFormatProperties)))
("properties" ::: Vector SparseImageFormatProperties)
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("properties" ::: Vector SparseImageFormatProperties)
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties))
-> ("properties" ::: Vector SparseImageFormatProperties)
-> ContT
("properties" ::: Vector SparseImageFormatProperties)
IO
("properties" ::: Vector SparseImageFormatProperties)
forall a b. (a -> b) -> a -> b
$ ("properties" ::: Vector SparseImageFormatProperties
pProperties')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkQueueBindSparse
:: FunPtr (Ptr Queue_T -> Word32 -> Ptr (BindSparseInfo a) -> Fence -> IO Result) -> Ptr Queue_T -> Word32 -> Ptr (BindSparseInfo a) -> Fence -> IO Result
queueBindSparse :: forall io . MonadIO io => Queue -> ("bindInfo" ::: Vector (SomeStruct BindSparseInfo)) -> Fence -> io ()
queueBindSparse :: Queue
-> ("bindInfo" ::: Vector (SomeStruct BindSparseInfo))
-> Fence
-> io ()
queueBindSparse queue :: Queue
queue bindInfo :: "bindInfo" ::: Vector (SomeStruct BindSparseInfo)
bindInfo fence :: Fence
fence = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkQueueBindSparsePtr :: FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
vkQueueBindSparsePtr = DeviceCmds
-> forall (a :: [*]).
FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo a))
-> Fence
-> IO Result)
pVkQueueBindSparse (Queue -> DeviceCmds
deviceCmds (Queue
queue :: Queue))
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
vkQueueBindSparsePtr FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
-> FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkQueueBindSparse is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkQueueBindSparse' :: Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result
vkQueueBindSparse' = FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
-> Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result
forall (a :: [*]).
FunPtr
(Ptr Queue_T
-> Word32 -> Ptr (BindSparseInfo a) -> Fence -> IO Result)
-> Ptr Queue_T
-> Word32
-> Ptr (BindSparseInfo a)
-> Fence
-> IO Result
mkVkQueueBindSparse FunPtr
(Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result)
vkQueueBindSparsePtr
"pBindInfo" ::: Ptr (BindSparseInfo Any)
pPBindInfo <- ((("pBindInfo" ::: Ptr (BindSparseInfo Any)) -> IO ()) -> IO ())
-> ContT () IO ("pBindInfo" ::: Ptr (BindSparseInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pBindInfo" ::: Ptr (BindSparseInfo Any)) -> IO ()) -> IO ())
-> ContT () IO ("pBindInfo" ::: Ptr (BindSparseInfo Any)))
-> ((("pBindInfo" ::: Ptr (BindSparseInfo Any)) -> IO ()) -> IO ())
-> ContT () IO ("pBindInfo" ::: Ptr (BindSparseInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pBindInfo" ::: Ptr (BindSparseInfo Any)) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(BindSparseInfo _) ((("bindInfo" ::: Vector (SomeStruct BindSparseInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("bindInfo" ::: Vector (SomeStruct BindSparseInfo)
bindInfo)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 96) 8
(Int -> SomeStruct BindSparseInfo -> ContT () IO ())
-> ("bindInfo" ::: Vector (SomeStruct BindSparseInfo))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct BindSparseInfo
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct BindSparseInfo)
-> SomeStruct BindSparseInfo -> IO () -> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Ptr (SomeStruct BindSparseInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ("pBindInfo" ::: Ptr (BindSparseInfo Any)
pPBindInfo ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Int -> Ptr (BindSparseInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (96 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (BindSparseInfo _))) (SomeStruct BindSparseInfo
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("bindInfo" ::: Vector (SomeStruct BindSparseInfo)
bindInfo)
Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Queue_T
-> Word32
-> ("pBindInfo" ::: Ptr (BindSparseInfo Any))
-> Fence
-> IO Result
vkQueueBindSparse' (Queue -> Ptr Queue_T
queueHandle (Queue
queue)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("bindInfo" ::: Vector (SomeStruct BindSparseInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("bindInfo" ::: Vector (SomeStruct BindSparseInfo)) -> Int)
-> ("bindInfo" ::: Vector (SomeStruct BindSparseInfo)) -> Int
forall a b. (a -> b) -> a -> b
$ ("bindInfo" ::: Vector (SomeStruct BindSparseInfo)
bindInfo)) :: Word32)) ("pBindInfo" ::: Ptr (BindSparseInfo Any)
pPBindInfo) (Fence
fence)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
data SparseImageFormatProperties = SparseImageFormatProperties
{
SparseImageFormatProperties -> ImageAspectFlags
aspectMask :: ImageAspectFlags
,
SparseImageFormatProperties -> Extent3D
imageGranularity :: Extent3D
,
SparseImageFormatProperties -> SparseImageFormatFlags
flags :: SparseImageFormatFlags
}
deriving (Typeable)
deriving instance Show SparseImageFormatProperties
instance ToCStruct SparseImageFormatProperties where
withCStruct :: SparseImageFormatProperties
-> (("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b)
-> IO b
withCStruct x :: SparseImageFormatProperties
x f :: ("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b
f = Int
-> Int
-> (("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 20 4 ((("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b)
-> IO b)
-> (("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pProperties" ::: Ptr SparseImageFormatProperties
p -> ("pProperties" ::: Ptr SparseImageFormatProperties)
-> SparseImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr SparseImageFormatProperties
p SparseImageFormatProperties
x (("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b
f "pProperties" ::: Ptr SparseImageFormatProperties
p)
pokeCStruct :: ("pProperties" ::: Ptr SparseImageFormatProperties)
-> SparseImageFormatProperties -> IO b -> IO b
pokeCStruct p :: "pProperties" ::: Ptr SparseImageFormatProperties
p SparseImageFormatProperties{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Extent3D)) (Extent3D
imageGranularity) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageFormatFlags -> SparseImageFormatFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr SparseImageFormatFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SparseImageFormatFlags)) (SparseImageFormatFlags
flags)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 20
cStructAlignment :: Int
cStructAlignment = 4
pokeZeroCStruct :: ("pProperties" ::: Ptr SparseImageFormatProperties) -> IO b -> IO b
pokeZeroCStruct p :: "pProperties" ::: Ptr SparseImageFormatProperties
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Extent3D)) (Extent3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SparseImageFormatProperties where
peekCStruct :: ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO SparseImageFormatProperties
peekCStruct p :: "pProperties" ::: Ptr SparseImageFormatProperties
p = do
ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags))
Extent3D
imageGranularity <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Extent3D))
SparseImageFormatFlags
flags <- Ptr SparseImageFormatFlags -> IO SparseImageFormatFlags
forall a. Storable a => Ptr a -> IO a
peek @SparseImageFormatFlags (("pProperties" ::: Ptr SparseImageFormatProperties
p ("pProperties" ::: Ptr SparseImageFormatProperties)
-> Int -> Ptr SparseImageFormatFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SparseImageFormatFlags))
SparseImageFormatProperties -> IO SparseImageFormatProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseImageFormatProperties -> IO SparseImageFormatProperties)
-> SparseImageFormatProperties -> IO SparseImageFormatProperties
forall a b. (a -> b) -> a -> b
$ ImageAspectFlags
-> Extent3D
-> SparseImageFormatFlags
-> SparseImageFormatProperties
SparseImageFormatProperties
ImageAspectFlags
aspectMask Extent3D
imageGranularity SparseImageFormatFlags
flags
instance Zero SparseImageFormatProperties where
zero :: SparseImageFormatProperties
zero = ImageAspectFlags
-> Extent3D
-> SparseImageFormatFlags
-> SparseImageFormatProperties
SparseImageFormatProperties
ImageAspectFlags
forall a. Zero a => a
zero
Extent3D
forall a. Zero a => a
zero
SparseImageFormatFlags
forall a. Zero a => a
zero
data SparseImageMemoryRequirements = SparseImageMemoryRequirements
{
SparseImageMemoryRequirements -> SparseImageFormatProperties
formatProperties :: SparseImageFormatProperties
,
SparseImageMemoryRequirements -> Word32
imageMipTailFirstLod :: Word32
,
SparseImageMemoryRequirements -> DeviceSize
imageMipTailSize :: DeviceSize
,
SparseImageMemoryRequirements -> DeviceSize
imageMipTailOffset :: DeviceSize
,
SparseImageMemoryRequirements -> DeviceSize
imageMipTailStride :: DeviceSize
}
deriving (Typeable)
deriving instance Show SparseImageMemoryRequirements
instance ToCStruct SparseImageMemoryRequirements where
withCStruct :: SparseImageMemoryRequirements
-> (("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO b)
-> IO b
withCStruct x :: SparseImageMemoryRequirements
x f :: ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO b
f = Int
-> Int
-> (("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO b)
-> IO b)
-> (("pSparseMemoryRequirements"
::: Ptr SparseImageMemoryRequirements)
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p -> ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> SparseImageMemoryRequirements -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p SparseImageMemoryRequirements
x (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO b
f "pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p)
pokeCStruct :: ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> SparseImageMemoryRequirements -> IO b -> IO b
pokeCStruct p :: "pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p SparseImageMemoryRequirements{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr SparseImageFormatProperties)
-> SparseImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr SparseImageFormatProperties)) (SparseImageFormatProperties
formatProperties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
imageMipTailFirstLod)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
imageMipTailSize)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
imageMipTailOffset)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) (DeviceSize
imageMipTailStride)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 48
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO b -> IO b
pokeZeroCStruct p :: "pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr SparseImageFormatProperties)
-> SparseImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr SparseImageFormatProperties)) (SparseImageFormatProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SparseImageMemoryRequirements where
peekCStruct :: ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> IO SparseImageMemoryRequirements
peekCStruct p :: "pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p = do
SparseImageFormatProperties
formatProperties <- ("pProperties" ::: Ptr SparseImageFormatProperties)
-> IO SparseImageFormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageFormatProperties (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr SparseImageFormatProperties))
Word32
imageMipTailFirstLod <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
DeviceSize
imageMipTailSize <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
DeviceSize
imageMipTailOffset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
DeviceSize
imageMipTailStride <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements
p ("pSparseMemoryRequirements" ::: Ptr SparseImageMemoryRequirements)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize))
SparseImageMemoryRequirements -> IO SparseImageMemoryRequirements
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseImageMemoryRequirements -> IO SparseImageMemoryRequirements)
-> SparseImageMemoryRequirements
-> IO SparseImageMemoryRequirements
forall a b. (a -> b) -> a -> b
$ SparseImageFormatProperties
-> Word32
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> SparseImageMemoryRequirements
SparseImageMemoryRequirements
SparseImageFormatProperties
formatProperties Word32
imageMipTailFirstLod DeviceSize
imageMipTailSize DeviceSize
imageMipTailOffset DeviceSize
imageMipTailStride
instance Zero SparseImageMemoryRequirements where
zero :: SparseImageMemoryRequirements
zero = SparseImageFormatProperties
-> Word32
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> SparseImageMemoryRequirements
SparseImageMemoryRequirements
SparseImageFormatProperties
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
data SparseMemoryBind = SparseMemoryBind
{
SparseMemoryBind -> DeviceSize
resourceOffset :: DeviceSize
,
SparseMemoryBind -> DeviceSize
size :: DeviceSize
,
SparseMemoryBind -> DeviceMemory
memory :: DeviceMemory
,
SparseMemoryBind -> DeviceSize
memoryOffset :: DeviceSize
,
SparseMemoryBind -> SparseMemoryBindFlags
flags :: SparseMemoryBindFlags
}
deriving (Typeable)
deriving instance Show SparseMemoryBind
instance ToCStruct SparseMemoryBind where
withCStruct :: SparseMemoryBind -> (Ptr SparseMemoryBind -> IO b) -> IO b
withCStruct x :: SparseMemoryBind
x f :: Ptr SparseMemoryBind -> IO b
f = Int -> Int -> (Ptr SparseMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> (Ptr SparseMemoryBind -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SparseMemoryBind
p -> Ptr SparseMemoryBind -> SparseMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SparseMemoryBind
p SparseMemoryBind
x (Ptr SparseMemoryBind -> IO b
f Ptr SparseMemoryBind
p)
pokeCStruct :: Ptr SparseMemoryBind -> SparseMemoryBind -> IO b -> IO b
pokeCStruct p :: Ptr SparseMemoryBind
p SparseMemoryBind{..} f :: IO b
f = do
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) (DeviceSize
resourceOffset)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) (DeviceSize
size)
Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceMemory)) (DeviceMemory
memory)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
memoryOffset)
Ptr SparseMemoryBindFlags -> SparseMemoryBindFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBindFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr SparseMemoryBindFlags)) (SparseMemoryBindFlags
flags)
IO b
f
cStructSize :: Int
cStructSize = 40
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr SparseMemoryBind -> IO b -> IO b
pokeZeroCStruct p :: Ptr SparseMemoryBind
p f :: IO b
f = do
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SparseMemoryBind where
peekCStruct :: Ptr SparseMemoryBind -> IO SparseMemoryBind
peekCStruct p :: Ptr SparseMemoryBind
p = do
DeviceSize
resourceOffset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
DeviceSize
size <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceMemory))
DeviceSize
memoryOffset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
SparseMemoryBindFlags
flags <- Ptr SparseMemoryBindFlags -> IO SparseMemoryBindFlags
forall a. Storable a => Ptr a -> IO a
peek @SparseMemoryBindFlags ((Ptr SparseMemoryBind
p Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBindFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr SparseMemoryBindFlags))
SparseMemoryBind -> IO SparseMemoryBind
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseMemoryBind -> IO SparseMemoryBind)
-> SparseMemoryBind -> IO SparseMemoryBind
forall a b. (a -> b) -> a -> b
$ DeviceSize
-> DeviceSize
-> DeviceMemory
-> DeviceSize
-> SparseMemoryBindFlags
-> SparseMemoryBind
SparseMemoryBind
DeviceSize
resourceOffset DeviceSize
size DeviceMemory
memory DeviceSize
memoryOffset SparseMemoryBindFlags
flags
instance Storable SparseMemoryBind where
sizeOf :: SparseMemoryBind -> Int
sizeOf ~SparseMemoryBind
_ = 40
alignment :: SparseMemoryBind -> Int
alignment ~SparseMemoryBind
_ = 8
peek :: Ptr SparseMemoryBind -> IO SparseMemoryBind
peek = Ptr SparseMemoryBind -> IO SparseMemoryBind
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr SparseMemoryBind -> SparseMemoryBind -> IO ()
poke ptr :: Ptr SparseMemoryBind
ptr poked :: SparseMemoryBind
poked = Ptr SparseMemoryBind -> SparseMemoryBind -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SparseMemoryBind
ptr SparseMemoryBind
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SparseMemoryBind where
zero :: SparseMemoryBind
zero = DeviceSize
-> DeviceSize
-> DeviceMemory
-> DeviceSize
-> SparseMemoryBindFlags
-> SparseMemoryBind
SparseMemoryBind
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceMemory
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
SparseMemoryBindFlags
forall a. Zero a => a
zero
data SparseImageMemoryBind = SparseImageMemoryBind
{
SparseImageMemoryBind -> ImageSubresource
subresource :: ImageSubresource
,
SparseImageMemoryBind -> Offset3D
offset :: Offset3D
,
SparseImageMemoryBind -> Extent3D
extent :: Extent3D
,
SparseImageMemoryBind -> DeviceMemory
memory :: DeviceMemory
,
SparseImageMemoryBind -> DeviceSize
memoryOffset :: DeviceSize
,
SparseImageMemoryBind -> SparseMemoryBindFlags
flags :: SparseMemoryBindFlags
}
deriving (Typeable)
deriving instance Show SparseImageMemoryBind
instance ToCStruct SparseImageMemoryBind where
withCStruct :: SparseImageMemoryBind
-> (Ptr SparseImageMemoryBind -> IO b) -> IO b
withCStruct x :: SparseImageMemoryBind
x f :: Ptr SparseImageMemoryBind -> IO b
f = Int -> Int -> (Ptr SparseImageMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> (Ptr SparseImageMemoryBind -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SparseImageMemoryBind
p -> Ptr SparseImageMemoryBind -> SparseImageMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SparseImageMemoryBind
p SparseImageMemoryBind
x (Ptr SparseImageMemoryBind -> IO b
f Ptr SparseImageMemoryBind
p)
pokeCStruct :: Ptr SparseImageMemoryBind -> SparseImageMemoryBind -> IO b -> IO b
pokeCStruct p :: Ptr SparseImageMemoryBind
p SparseImageMemoryBind{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresource -> ImageSubresource -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr ImageSubresource
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresource)) (ImageSubresource
subresource) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D)) (Offset3D
offset) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Extent3D)) (Extent3D
extent) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceMemory)) (DeviceMemory
memory)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) (DeviceSize
memoryOffset)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseMemoryBindFlags -> SparseMemoryBindFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr SparseMemoryBindFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr SparseMemoryBindFlags)) (SparseMemoryBindFlags
flags)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 64
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr SparseImageMemoryBind -> IO b -> IO b
pokeZeroCStruct p :: Ptr SparseImageMemoryBind
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresource -> ImageSubresource -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr ImageSubresource
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresource)) (ImageSubresource
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D)) (Offset3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Extent3D)) (Extent3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SparseImageMemoryBind where
peekCStruct :: Ptr SparseImageMemoryBind -> IO SparseImageMemoryBind
peekCStruct p :: Ptr SparseImageMemoryBind
p = do
ImageSubresource
subresource <- Ptr ImageSubresource -> IO ImageSubresource
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresource ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr ImageSubresource
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresource))
Offset3D
offset <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D))
Extent3D
extent <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Extent3D))
DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceMemory))
DeviceSize
memoryOffset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize))
SparseMemoryBindFlags
flags <- Ptr SparseMemoryBindFlags -> IO SparseMemoryBindFlags
forall a. Storable a => Ptr a -> IO a
peek @SparseMemoryBindFlags ((Ptr SparseImageMemoryBind
p Ptr SparseImageMemoryBind -> Int -> Ptr SparseMemoryBindFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr SparseMemoryBindFlags))
SparseImageMemoryBind -> IO SparseImageMemoryBind
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseImageMemoryBind -> IO SparseImageMemoryBind)
-> SparseImageMemoryBind -> IO SparseImageMemoryBind
forall a b. (a -> b) -> a -> b
$ ImageSubresource
-> Offset3D
-> Extent3D
-> DeviceMemory
-> DeviceSize
-> SparseMemoryBindFlags
-> SparseImageMemoryBind
SparseImageMemoryBind
ImageSubresource
subresource Offset3D
offset Extent3D
extent DeviceMemory
memory DeviceSize
memoryOffset SparseMemoryBindFlags
flags
instance Zero SparseImageMemoryBind where
zero :: SparseImageMemoryBind
zero = ImageSubresource
-> Offset3D
-> Extent3D
-> DeviceMemory
-> DeviceSize
-> SparseMemoryBindFlags
-> SparseImageMemoryBind
SparseImageMemoryBind
ImageSubresource
forall a. Zero a => a
zero
Offset3D
forall a. Zero a => a
zero
Extent3D
forall a. Zero a => a
zero
DeviceMemory
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
SparseMemoryBindFlags
forall a. Zero a => a
zero
data SparseBufferMemoryBindInfo = SparseBufferMemoryBindInfo
{
SparseBufferMemoryBindInfo -> Buffer
buffer :: Buffer
,
SparseBufferMemoryBindInfo -> Vector SparseMemoryBind
binds :: Vector SparseMemoryBind
}
deriving (Typeable)
deriving instance Show SparseBufferMemoryBindInfo
instance ToCStruct SparseBufferMemoryBindInfo where
withCStruct :: SparseBufferMemoryBindInfo
-> (Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b
withCStruct x :: SparseBufferMemoryBindInfo
x f :: Ptr SparseBufferMemoryBindInfo -> IO b
f = Int -> Int -> (Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> (Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SparseBufferMemoryBindInfo
p -> Ptr SparseBufferMemoryBindInfo
-> SparseBufferMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SparseBufferMemoryBindInfo
p SparseBufferMemoryBindInfo
x (Ptr SparseBufferMemoryBindInfo -> IO b
f Ptr SparseBufferMemoryBindInfo
p)
pokeCStruct :: Ptr SparseBufferMemoryBindInfo
-> SparseBufferMemoryBindInfo -> IO b -> IO b
pokeCStruct p :: Ptr SparseBufferMemoryBindInfo
p SparseBufferMemoryBindInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Buffer)) (Buffer
buffer)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SparseMemoryBind -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseMemoryBind -> Int) -> Vector SparseMemoryBind -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SparseMemoryBind
binds)) :: Word32))
Ptr SparseMemoryBind
pPBinds' <- ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind))
-> ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseMemoryBind ((Vector SparseMemoryBind -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseMemoryBind
binds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
(Int -> SparseMemoryBind -> ContT b IO ())
-> Vector SparseMemoryBind -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseMemoryBind
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseMemoryBind -> SparseMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseMemoryBind
pPBinds' Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBind
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseMemoryBind) (SparseMemoryBind
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseMemoryBind
binds)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseMemoryBind) -> Ptr SparseMemoryBind -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo -> Int -> Ptr (Ptr SparseMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseMemoryBind))) (Ptr SparseMemoryBind
pPBinds')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr SparseBufferMemoryBindInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr SparseBufferMemoryBindInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
Ptr SparseMemoryBind
pPBinds' <- ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind))
-> ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseMemoryBind ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
(Int -> SparseMemoryBind -> ContT b IO ())
-> Vector SparseMemoryBind -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseMemoryBind
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseMemoryBind -> SparseMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseMemoryBind
pPBinds' Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBind
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseMemoryBind) (SparseMemoryBind
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseMemoryBind
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseMemoryBind) -> Ptr SparseMemoryBind -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo -> Int -> Ptr (Ptr SparseMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseMemoryBind))) (Ptr SparseMemoryBind
pPBinds')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SparseBufferMemoryBindInfo where
peekCStruct :: Ptr SparseBufferMemoryBindInfo -> IO SparseBufferMemoryBindInfo
peekCStruct p :: Ptr SparseBufferMemoryBindInfo
p = do
Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Buffer))
Word32
bindCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
Ptr SparseMemoryBind
pBinds <- Ptr (Ptr SparseMemoryBind) -> IO (Ptr SparseMemoryBind)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SparseMemoryBind) ((Ptr SparseBufferMemoryBindInfo
p Ptr SparseBufferMemoryBindInfo -> Int -> Ptr (Ptr SparseMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseMemoryBind)))
Vector SparseMemoryBind
pBinds' <- Int -> (Int -> IO SparseMemoryBind) -> IO (Vector SparseMemoryBind)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
bindCount) (\i :: Int
i -> Ptr SparseMemoryBind -> IO SparseMemoryBind
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseMemoryBind ((Ptr SparseMemoryBind
pBinds Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBind
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseMemoryBind)))
SparseBufferMemoryBindInfo -> IO SparseBufferMemoryBindInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseBufferMemoryBindInfo -> IO SparseBufferMemoryBindInfo)
-> SparseBufferMemoryBindInfo -> IO SparseBufferMemoryBindInfo
forall a b. (a -> b) -> a -> b
$ Buffer -> Vector SparseMemoryBind -> SparseBufferMemoryBindInfo
SparseBufferMemoryBindInfo
Buffer
buffer Vector SparseMemoryBind
pBinds'
instance Zero SparseBufferMemoryBindInfo where
zero :: SparseBufferMemoryBindInfo
zero = Buffer -> Vector SparseMemoryBind -> SparseBufferMemoryBindInfo
SparseBufferMemoryBindInfo
Buffer
forall a. Zero a => a
zero
Vector SparseMemoryBind
forall a. Monoid a => a
mempty
data SparseImageOpaqueMemoryBindInfo = SparseImageOpaqueMemoryBindInfo
{
SparseImageOpaqueMemoryBindInfo -> Image
image :: Image
,
SparseImageOpaqueMemoryBindInfo -> Vector SparseMemoryBind
binds :: Vector SparseMemoryBind
}
deriving (Typeable)
deriving instance Show SparseImageOpaqueMemoryBindInfo
instance ToCStruct SparseImageOpaqueMemoryBindInfo where
withCStruct :: SparseImageOpaqueMemoryBindInfo
-> (Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b
withCStruct x :: SparseImageOpaqueMemoryBindInfo
x f :: Ptr SparseImageOpaqueMemoryBindInfo -> IO b
f = Int -> Int -> (Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> (Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SparseImageOpaqueMemoryBindInfo
p -> Ptr SparseImageOpaqueMemoryBindInfo
-> SparseImageOpaqueMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SparseImageOpaqueMemoryBindInfo
p SparseImageOpaqueMemoryBindInfo
x (Ptr SparseImageOpaqueMemoryBindInfo -> IO b
f Ptr SparseImageOpaqueMemoryBindInfo
p)
pokeCStruct :: Ptr SparseImageOpaqueMemoryBindInfo
-> SparseImageOpaqueMemoryBindInfo -> IO b -> IO b
pokeCStruct p :: Ptr SparseImageOpaqueMemoryBindInfo
p SparseImageOpaqueMemoryBindInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Image)) (Image
image)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SparseMemoryBind -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseMemoryBind -> Int) -> Vector SparseMemoryBind -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SparseMemoryBind
binds)) :: Word32))
Ptr SparseMemoryBind
pPBinds' <- ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind))
-> ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseMemoryBind ((Vector SparseMemoryBind -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseMemoryBind
binds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
(Int -> SparseMemoryBind -> ContT b IO ())
-> Vector SparseMemoryBind -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseMemoryBind
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseMemoryBind -> SparseMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseMemoryBind
pPBinds' Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBind
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseMemoryBind) (SparseMemoryBind
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseMemoryBind
binds)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseMemoryBind) -> Ptr SparseMemoryBind -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> Ptr (Ptr SparseMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseMemoryBind))) (Ptr SparseMemoryBind
pPBinds')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr SparseImageOpaqueMemoryBindInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr SparseImageOpaqueMemoryBindInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Image)) (Image
forall a. Zero a => a
zero)
Ptr SparseMemoryBind
pPBinds' <- ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind))
-> ((Ptr SparseMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseMemoryBind)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseMemoryBind ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
(Int -> SparseMemoryBind -> ContT b IO ())
-> Vector SparseMemoryBind -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseMemoryBind
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseMemoryBind -> SparseMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseMemoryBind
pPBinds' Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBind
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseMemoryBind) (SparseMemoryBind
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseMemoryBind
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseMemoryBind) -> Ptr SparseMemoryBind -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> Ptr (Ptr SparseMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseMemoryBind))) (Ptr SparseMemoryBind
pPBinds')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SparseImageOpaqueMemoryBindInfo where
peekCStruct :: Ptr SparseImageOpaqueMemoryBindInfo
-> IO SparseImageOpaqueMemoryBindInfo
peekCStruct p :: Ptr SparseImageOpaqueMemoryBindInfo
p = do
Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Image))
Word32
bindCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
Ptr SparseMemoryBind
pBinds <- Ptr (Ptr SparseMemoryBind) -> IO (Ptr SparseMemoryBind)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SparseMemoryBind) ((Ptr SparseImageOpaqueMemoryBindInfo
p Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> Ptr (Ptr SparseMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseMemoryBind)))
Vector SparseMemoryBind
pBinds' <- Int -> (Int -> IO SparseMemoryBind) -> IO (Vector SparseMemoryBind)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
bindCount) (\i :: Int
i -> Ptr SparseMemoryBind -> IO SparseMemoryBind
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseMemoryBind ((Ptr SparseMemoryBind
pBinds Ptr SparseMemoryBind -> Int -> Ptr SparseMemoryBind
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseMemoryBind)))
SparseImageOpaqueMemoryBindInfo
-> IO SparseImageOpaqueMemoryBindInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseImageOpaqueMemoryBindInfo
-> IO SparseImageOpaqueMemoryBindInfo)
-> SparseImageOpaqueMemoryBindInfo
-> IO SparseImageOpaqueMemoryBindInfo
forall a b. (a -> b) -> a -> b
$ Image -> Vector SparseMemoryBind -> SparseImageOpaqueMemoryBindInfo
SparseImageOpaqueMemoryBindInfo
Image
image Vector SparseMemoryBind
pBinds'
instance Zero SparseImageOpaqueMemoryBindInfo where
zero :: SparseImageOpaqueMemoryBindInfo
zero = Image -> Vector SparseMemoryBind -> SparseImageOpaqueMemoryBindInfo
SparseImageOpaqueMemoryBindInfo
Image
forall a. Zero a => a
zero
Vector SparseMemoryBind
forall a. Monoid a => a
mempty
data SparseImageMemoryBindInfo = SparseImageMemoryBindInfo
{
SparseImageMemoryBindInfo -> Image
image :: Image
,
SparseImageMemoryBindInfo -> Vector SparseImageMemoryBind
binds :: Vector SparseImageMemoryBind
}
deriving (Typeable)
deriving instance Show SparseImageMemoryBindInfo
instance ToCStruct SparseImageMemoryBindInfo where
withCStruct :: SparseImageMemoryBindInfo
-> (Ptr SparseImageMemoryBindInfo -> IO b) -> IO b
withCStruct x :: SparseImageMemoryBindInfo
x f :: Ptr SparseImageMemoryBindInfo -> IO b
f = Int -> Int -> (Ptr SparseImageMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> (Ptr SparseImageMemoryBindInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SparseImageMemoryBindInfo
p -> Ptr SparseImageMemoryBindInfo
-> SparseImageMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SparseImageMemoryBindInfo
p SparseImageMemoryBindInfo
x (Ptr SparseImageMemoryBindInfo -> IO b
f Ptr SparseImageMemoryBindInfo
p)
pokeCStruct :: Ptr SparseImageMemoryBindInfo
-> SparseImageMemoryBindInfo -> IO b -> IO b
pokeCStruct p :: Ptr SparseImageMemoryBindInfo
p SparseImageMemoryBindInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Image)) (Image
image)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SparseImageMemoryBind -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseImageMemoryBind -> Int)
-> Vector SparseImageMemoryBind -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SparseImageMemoryBind
binds)) :: Word32))
Ptr SparseImageMemoryBind
pPBinds' <- ((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBind)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBind))
-> ((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBind)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseImageMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseImageMemoryBind ((Vector SparseImageMemoryBind -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseImageMemoryBind
binds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 64) 8
(Int -> SparseImageMemoryBind -> ContT b IO ())
-> Vector SparseImageMemoryBind -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseImageMemoryBind
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageMemoryBind -> SparseImageMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseImageMemoryBind
pPBinds' Ptr SparseImageMemoryBind -> Int -> Ptr SparseImageMemoryBind
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (64 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryBind) (SparseImageMemoryBind
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseImageMemoryBind
binds)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseImageMemoryBind)
-> Ptr SparseImageMemoryBind -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo
-> Int -> Ptr (Ptr SparseImageMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseImageMemoryBind))) (Ptr SparseImageMemoryBind
pPBinds')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr SparseImageMemoryBindInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr SparseImageMemoryBindInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Image)) (Image
forall a. Zero a => a
zero)
Ptr SparseImageMemoryBind
pPBinds' <- ((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBind)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBind))
-> ((Ptr SparseImageMemoryBind -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBind)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseImageMemoryBind -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseImageMemoryBind ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 64) 8
(Int -> SparseImageMemoryBind -> ContT b IO ())
-> Vector SparseImageMemoryBind -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseImageMemoryBind
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageMemoryBind -> SparseImageMemoryBind -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseImageMemoryBind
pPBinds' Ptr SparseImageMemoryBind -> Int -> Ptr SparseImageMemoryBind
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (64 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryBind) (SparseImageMemoryBind
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseImageMemoryBind
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseImageMemoryBind)
-> Ptr SparseImageMemoryBind -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo
-> Int -> Ptr (Ptr SparseImageMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseImageMemoryBind))) (Ptr SparseImageMemoryBind
pPBinds')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SparseImageMemoryBindInfo where
peekCStruct :: Ptr SparseImageMemoryBindInfo -> IO SparseImageMemoryBindInfo
peekCStruct p :: Ptr SparseImageMemoryBindInfo
p = do
Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Image))
Word32
bindCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
Ptr SparseImageMemoryBind
pBinds <- Ptr (Ptr SparseImageMemoryBind) -> IO (Ptr SparseImageMemoryBind)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SparseImageMemoryBind) ((Ptr SparseImageMemoryBindInfo
p Ptr SparseImageMemoryBindInfo
-> Int -> Ptr (Ptr SparseImageMemoryBind)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SparseImageMemoryBind)))
Vector SparseImageMemoryBind
pBinds' <- Int
-> (Int -> IO SparseImageMemoryBind)
-> IO (Vector SparseImageMemoryBind)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
bindCount) (\i :: Int
i -> Ptr SparseImageMemoryBind -> IO SparseImageMemoryBind
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageMemoryBind ((Ptr SparseImageMemoryBind
pBinds Ptr SparseImageMemoryBind -> Int -> Ptr SparseImageMemoryBind
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (64 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryBind)))
SparseImageMemoryBindInfo -> IO SparseImageMemoryBindInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseImageMemoryBindInfo -> IO SparseImageMemoryBindInfo)
-> SparseImageMemoryBindInfo -> IO SparseImageMemoryBindInfo
forall a b. (a -> b) -> a -> b
$ Image -> Vector SparseImageMemoryBind -> SparseImageMemoryBindInfo
SparseImageMemoryBindInfo
Image
image Vector SparseImageMemoryBind
pBinds'
instance Zero SparseImageMemoryBindInfo where
zero :: SparseImageMemoryBindInfo
zero = Image -> Vector SparseImageMemoryBind -> SparseImageMemoryBindInfo
SparseImageMemoryBindInfo
Image
forall a. Zero a => a
zero
Vector SparseImageMemoryBind
forall a. Monoid a => a
mempty
data BindSparseInfo (es :: [Type]) = BindSparseInfo
{
BindSparseInfo es -> Chain es
next :: Chain es
,
BindSparseInfo es -> Vector Semaphore
waitSemaphores :: Vector Semaphore
,
BindSparseInfo es -> Vector SparseBufferMemoryBindInfo
bufferBinds :: Vector SparseBufferMemoryBindInfo
,
BindSparseInfo es -> Vector SparseImageOpaqueMemoryBindInfo
imageOpaqueBinds :: Vector SparseImageOpaqueMemoryBindInfo
,
BindSparseInfo es -> Vector SparseImageMemoryBindInfo
imageBinds :: Vector SparseImageMemoryBindInfo
,
BindSparseInfo es -> Vector Semaphore
signalSemaphores :: Vector Semaphore
}
deriving (Typeable)
deriving instance Show (Chain es) => Show (BindSparseInfo es)
instance Extensible BindSparseInfo where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_BIND_SPARSE_INFO
setNext :: BindSparseInfo ds -> Chain es -> BindSparseInfo es
setNext x :: BindSparseInfo ds
x next :: Chain es
next = BindSparseInfo ds
x{$sel:next:BindSparseInfo :: Chain es
next = Chain es
next}
getNext :: BindSparseInfo es -> Chain es
getNext BindSparseInfo{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends BindSparseInfo e => b) -> Maybe b
extends :: proxy e -> (Extends BindSparseInfo e => b) -> Maybe b
extends _ f :: Extends BindSparseInfo e => b
f
| Just Refl <- (Typeable e, Typeable TimelineSemaphoreSubmitInfo) =>
Maybe (e :~: TimelineSemaphoreSubmitInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @TimelineSemaphoreSubmitInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BindSparseInfo e => b
f
| Just Refl <- (Typeable e, Typeable DeviceGroupBindSparseInfo) =>
Maybe (e :~: DeviceGroupBindSparseInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceGroupBindSparseInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BindSparseInfo e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss BindSparseInfo es, PokeChain es) => ToCStruct (BindSparseInfo es) where
withCStruct :: BindSparseInfo es -> (Ptr (BindSparseInfo es) -> IO b) -> IO b
withCStruct x :: BindSparseInfo es
x f :: Ptr (BindSparseInfo es) -> IO b
f = Int -> Int -> (Ptr (BindSparseInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 96 8 ((Ptr (BindSparseInfo es) -> IO b) -> IO b)
-> (Ptr (BindSparseInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (BindSparseInfo es)
p -> Ptr (BindSparseInfo es) -> BindSparseInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (BindSparseInfo es)
p BindSparseInfo es
x (Ptr (BindSparseInfo es) -> IO b
f Ptr (BindSparseInfo es)
p)
pokeCStruct :: Ptr (BindSparseInfo es) -> BindSparseInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (BindSparseInfo es)
p BindSparseInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_SPARSE_INFO)
Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore -> Int) -> Vector Semaphore -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Semaphore
waitSemaphores)) :: Word32))
Ptr Semaphore
pPWaitSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore
waitSemaphores)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPWaitSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
waitSemaphores)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPWaitSemaphores')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SparseBufferMemoryBindInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseBufferMemoryBindInfo -> Int)
-> Vector SparseBufferMemoryBindInfo -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SparseBufferMemoryBindInfo
bufferBinds)) :: Word32))
Ptr SparseBufferMemoryBindInfo
pPBufferBinds' <- ((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseBufferMemoryBindInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseBufferMemoryBindInfo))
-> ((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseBufferMemoryBindInfo)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseBufferMemoryBindInfo ((Vector SparseBufferMemoryBindInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseBufferMemoryBindInfo
bufferBinds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int -> SparseBufferMemoryBindInfo -> ContT b IO ())
-> Vector SparseBufferMemoryBindInfo -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseBufferMemoryBindInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseBufferMemoryBindInfo
-> SparseBufferMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseBufferMemoryBindInfo
pPBufferBinds' Ptr SparseBufferMemoryBindInfo
-> Int -> Ptr SparseBufferMemoryBindInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseBufferMemoryBindInfo) (SparseBufferMemoryBindInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseBufferMemoryBindInfo
bufferBinds)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseBufferMemoryBindInfo)
-> Ptr SparseBufferMemoryBindInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseBufferMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SparseBufferMemoryBindInfo))) (Ptr SparseBufferMemoryBindInfo
pPBufferBinds')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SparseImageOpaqueMemoryBindInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseImageOpaqueMemoryBindInfo -> Int)
-> Vector SparseImageOpaqueMemoryBindInfo -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SparseImageOpaqueMemoryBindInfo
imageOpaqueBinds)) :: Word32))
Ptr SparseImageOpaqueMemoryBindInfo
pPImageOpaqueBinds' <- ((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageOpaqueMemoryBindInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageOpaqueMemoryBindInfo))
-> ((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageOpaqueMemoryBindInfo)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseImageOpaqueMemoryBindInfo ((Vector SparseImageOpaqueMemoryBindInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseImageOpaqueMemoryBindInfo
imageOpaqueBinds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int -> SparseImageOpaqueMemoryBindInfo -> ContT b IO ())
-> Vector SparseImageOpaqueMemoryBindInfo -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseImageOpaqueMemoryBindInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageOpaqueMemoryBindInfo
-> SparseImageOpaqueMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseImageOpaqueMemoryBindInfo
pPImageOpaqueBinds' Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> Ptr SparseImageOpaqueMemoryBindInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageOpaqueMemoryBindInfo) (SparseImageOpaqueMemoryBindInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseImageOpaqueMemoryBindInfo
imageOpaqueBinds)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseImageOpaqueMemoryBindInfo)
-> Ptr SparseImageOpaqueMemoryBindInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseImageOpaqueMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SparseImageOpaqueMemoryBindInfo))) (Ptr SparseImageOpaqueMemoryBindInfo
pPImageOpaqueBinds')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SparseImageMemoryBindInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseImageMemoryBindInfo -> Int)
-> Vector SparseImageMemoryBindInfo -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SparseImageMemoryBindInfo
imageBinds)) :: Word32))
Ptr SparseImageMemoryBindInfo
pPImageBinds' <- ((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBindInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBindInfo))
-> ((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBindInfo)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseImageMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseImageMemoryBindInfo ((Vector SparseImageMemoryBindInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SparseImageMemoryBindInfo
imageBinds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int -> SparseImageMemoryBindInfo -> ContT b IO ())
-> Vector SparseImageMemoryBindInfo -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseImageMemoryBindInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageMemoryBindInfo
-> SparseImageMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseImageMemoryBindInfo
pPImageBinds' Ptr SparseImageMemoryBindInfo
-> Int -> Ptr SparseImageMemoryBindInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryBindInfo) (SparseImageMemoryBindInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseImageMemoryBindInfo
imageBinds)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseImageMemoryBindInfo)
-> Ptr SparseImageMemoryBindInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseImageMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr SparseImageMemoryBindInfo))) (Ptr SparseImageMemoryBindInfo
pPImageBinds')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore -> Int) -> Vector Semaphore -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Semaphore
signalSemaphores)) :: Word32))
Ptr Semaphore
pPSignalSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore
signalSemaphores)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPSignalSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
signalSemaphores)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPSignalSemaphores')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 96
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (BindSparseInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (BindSparseInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_SPARSE_INFO)
Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
Ptr Semaphore
pPWaitSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPWaitSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPWaitSemaphores')
Ptr SparseBufferMemoryBindInfo
pPBufferBinds' <- ((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseBufferMemoryBindInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseBufferMemoryBindInfo))
-> ((Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseBufferMemoryBindInfo)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseBufferMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseBufferMemoryBindInfo ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int -> SparseBufferMemoryBindInfo -> ContT b IO ())
-> Vector SparseBufferMemoryBindInfo -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseBufferMemoryBindInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseBufferMemoryBindInfo
-> SparseBufferMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseBufferMemoryBindInfo
pPBufferBinds' Ptr SparseBufferMemoryBindInfo
-> Int -> Ptr SparseBufferMemoryBindInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseBufferMemoryBindInfo) (SparseBufferMemoryBindInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseBufferMemoryBindInfo
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseBufferMemoryBindInfo)
-> Ptr SparseBufferMemoryBindInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseBufferMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SparseBufferMemoryBindInfo))) (Ptr SparseBufferMemoryBindInfo
pPBufferBinds')
Ptr SparseImageOpaqueMemoryBindInfo
pPImageOpaqueBinds' <- ((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageOpaqueMemoryBindInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageOpaqueMemoryBindInfo))
-> ((Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageOpaqueMemoryBindInfo)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseImageOpaqueMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseImageOpaqueMemoryBindInfo ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int -> SparseImageOpaqueMemoryBindInfo -> ContT b IO ())
-> Vector SparseImageOpaqueMemoryBindInfo -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseImageOpaqueMemoryBindInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageOpaqueMemoryBindInfo
-> SparseImageOpaqueMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseImageOpaqueMemoryBindInfo
pPImageOpaqueBinds' Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> Ptr SparseImageOpaqueMemoryBindInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageOpaqueMemoryBindInfo) (SparseImageOpaqueMemoryBindInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseImageOpaqueMemoryBindInfo
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseImageOpaqueMemoryBindInfo)
-> Ptr SparseImageOpaqueMemoryBindInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseImageOpaqueMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SparseImageOpaqueMemoryBindInfo))) (Ptr SparseImageOpaqueMemoryBindInfo
pPImageOpaqueBinds')
Ptr SparseImageMemoryBindInfo
pPImageBinds' <- ((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBindInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBindInfo))
-> ((Ptr SparseImageMemoryBindInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SparseImageMemoryBindInfo)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SparseImageMemoryBindInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SparseImageMemoryBindInfo ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int -> SparseImageMemoryBindInfo -> ContT b IO ())
-> Vector SparseImageMemoryBindInfo -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SparseImageMemoryBindInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageMemoryBindInfo
-> SparseImageMemoryBindInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SparseImageMemoryBindInfo
pPImageBinds' Ptr SparseImageMemoryBindInfo
-> Int -> Ptr SparseImageMemoryBindInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryBindInfo) (SparseImageMemoryBindInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SparseImageMemoryBindInfo
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SparseImageMemoryBindInfo)
-> Ptr SparseImageMemoryBindInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseImageMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr SparseImageMemoryBindInfo))) (Ptr SparseImageMemoryBindInfo
pPImageBinds')
Ptr Semaphore
pPSignalSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPSignalSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPSignalSemaphores')
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance (Extendss BindSparseInfo es, PeekChain es) => FromCStruct (BindSparseInfo es) where
peekCStruct :: Ptr (BindSparseInfo es) -> IO (BindSparseInfo es)
peekCStruct p :: Ptr (BindSparseInfo es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
Word32
waitSemaphoreCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
Ptr Semaphore
pWaitSemaphores <- Ptr (Ptr Semaphore) -> IO (Ptr Semaphore)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Semaphore) ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore)))
Vector Semaphore
pWaitSemaphores' <- Int -> (Int -> IO Semaphore) -> IO (Vector Semaphore)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
waitSemaphoreCount) (\i :: Int
i -> Ptr Semaphore -> IO Semaphore
forall a. Storable a => Ptr a -> IO a
peek @Semaphore ((Ptr Semaphore
pWaitSemaphores Ptr Semaphore -> Int -> Ptr Semaphore
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore)))
Word32
bufferBindCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
Ptr SparseBufferMemoryBindInfo
pBufferBinds <- Ptr (Ptr SparseBufferMemoryBindInfo)
-> IO (Ptr SparseBufferMemoryBindInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SparseBufferMemoryBindInfo) ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseBufferMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SparseBufferMemoryBindInfo)))
Vector SparseBufferMemoryBindInfo
pBufferBinds' <- Int
-> (Int -> IO SparseBufferMemoryBindInfo)
-> IO (Vector SparseBufferMemoryBindInfo)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
bufferBindCount) (\i :: Int
i -> Ptr SparseBufferMemoryBindInfo -> IO SparseBufferMemoryBindInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseBufferMemoryBindInfo ((Ptr SparseBufferMemoryBindInfo
pBufferBinds Ptr SparseBufferMemoryBindInfo
-> Int -> Ptr SparseBufferMemoryBindInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseBufferMemoryBindInfo)))
Word32
imageOpaqueBindCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
Ptr SparseImageOpaqueMemoryBindInfo
pImageOpaqueBinds <- Ptr (Ptr SparseImageOpaqueMemoryBindInfo)
-> IO (Ptr SparseImageOpaqueMemoryBindInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SparseImageOpaqueMemoryBindInfo) ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseImageOpaqueMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SparseImageOpaqueMemoryBindInfo)))
Vector SparseImageOpaqueMemoryBindInfo
pImageOpaqueBinds' <- Int
-> (Int -> IO SparseImageOpaqueMemoryBindInfo)
-> IO (Vector SparseImageOpaqueMemoryBindInfo)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
imageOpaqueBindCount) (\i :: Int
i -> Ptr SparseImageOpaqueMemoryBindInfo
-> IO SparseImageOpaqueMemoryBindInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageOpaqueMemoryBindInfo ((Ptr SparseImageOpaqueMemoryBindInfo
pImageOpaqueBinds Ptr SparseImageOpaqueMemoryBindInfo
-> Int -> Ptr SparseImageOpaqueMemoryBindInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageOpaqueMemoryBindInfo)))
Word32
imageBindCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
Ptr SparseImageMemoryBindInfo
pImageBinds <- Ptr (Ptr SparseImageMemoryBindInfo)
-> IO (Ptr SparseImageMemoryBindInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SparseImageMemoryBindInfo) ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> Ptr (Ptr SparseImageMemoryBindInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr SparseImageMemoryBindInfo)))
Vector SparseImageMemoryBindInfo
pImageBinds' <- Int
-> (Int -> IO SparseImageMemoryBindInfo)
-> IO (Vector SparseImageMemoryBindInfo)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
imageBindCount) (\i :: Int
i -> Ptr SparseImageMemoryBindInfo -> IO SparseImageMemoryBindInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageMemoryBindInfo ((Ptr SparseImageMemoryBindInfo
pImageBinds Ptr SparseImageMemoryBindInfo
-> Int -> Ptr SparseImageMemoryBindInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageMemoryBindInfo)))
Word32
signalSemaphoreCount <- ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es)
-> Int -> "pSparseMemoryRequirementCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32))
Ptr Semaphore
pSignalSemaphores <- Ptr (Ptr Semaphore) -> IO (Ptr Semaphore)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Semaphore) ((Ptr (BindSparseInfo es)
p Ptr (BindSparseInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr Semaphore)))
Vector Semaphore
pSignalSemaphores' <- Int -> (Int -> IO Semaphore) -> IO (Vector Semaphore)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
signalSemaphoreCount) (\i :: Int
i -> Ptr Semaphore -> IO Semaphore
forall a. Storable a => Ptr a -> IO a
peek @Semaphore ((Ptr Semaphore
pSignalSemaphores Ptr Semaphore -> Int -> Ptr Semaphore
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore)))
BindSparseInfo es -> IO (BindSparseInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BindSparseInfo es -> IO (BindSparseInfo es))
-> BindSparseInfo es -> IO (BindSparseInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Vector Semaphore
-> Vector SparseBufferMemoryBindInfo
-> Vector SparseImageOpaqueMemoryBindInfo
-> Vector SparseImageMemoryBindInfo
-> Vector Semaphore
-> BindSparseInfo es
forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector SparseBufferMemoryBindInfo
-> Vector SparseImageOpaqueMemoryBindInfo
-> Vector SparseImageMemoryBindInfo
-> Vector Semaphore
-> BindSparseInfo es
BindSparseInfo
Chain es
next Vector Semaphore
pWaitSemaphores' Vector SparseBufferMemoryBindInfo
pBufferBinds' Vector SparseImageOpaqueMemoryBindInfo
pImageOpaqueBinds' Vector SparseImageMemoryBindInfo
pImageBinds' Vector Semaphore
pSignalSemaphores'
instance es ~ '[] => Zero (BindSparseInfo es) where
zero :: BindSparseInfo es
zero = Chain es
-> Vector Semaphore
-> Vector SparseBufferMemoryBindInfo
-> Vector SparseImageOpaqueMemoryBindInfo
-> Vector SparseImageMemoryBindInfo
-> Vector Semaphore
-> BindSparseInfo es
forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector SparseBufferMemoryBindInfo
-> Vector SparseImageOpaqueMemoryBindInfo
-> Vector SparseImageMemoryBindInfo
-> Vector Semaphore
-> BindSparseInfo es
BindSparseInfo
()
Vector Semaphore
forall a. Monoid a => a
mempty
Vector SparseBufferMemoryBindInfo
forall a. Monoid a => a
mempty
Vector SparseImageOpaqueMemoryBindInfo
forall a. Monoid a => a
mempty
Vector SparseImageMemoryBindInfo
forall a. Monoid a => a
mempty
Vector Semaphore
forall a. Monoid a => a
mempty