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