{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_descriptor_buffer ( getDescriptorSetLayoutSizeEXT
, getDescriptorSetLayoutBindingOffsetEXT
, getDescriptorEXT
, cmdBindDescriptorBuffersEXT
, cmdSetDescriptorBufferOffsetsEXT
, cmdBindDescriptorBufferEmbeddedSamplersEXT
, getBufferOpaqueCaptureDescriptorDataEXT
, getImageOpaqueCaptureDescriptorDataEXT
, getImageViewOpaqueCaptureDescriptorDataEXT
, getSamplerOpaqueCaptureDescriptorDataEXT
, getAccelerationStructureOpaqueCaptureDescriptorDataEXT
, PhysicalDeviceDescriptorBufferFeaturesEXT(..)
, PhysicalDeviceDescriptorBufferPropertiesEXT(..)
, PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT(..)
, DescriptorAddressInfoEXT(..)
, DescriptorBufferBindingInfoEXT(..)
, DescriptorBufferBindingPushDescriptorBufferHandleEXT(..)
, DescriptorGetInfoEXT(..)
, BufferCaptureDescriptorDataInfoEXT(..)
, ImageCaptureDescriptorDataInfoEXT(..)
, ImageViewCaptureDescriptorDataInfoEXT(..)
, SamplerCaptureDescriptorDataInfoEXT(..)
, AccelerationStructureCaptureDescriptorDataInfoEXT(..)
, OpaqueCaptureDescriptorDataCreateInfoEXT(..)
, DescriptorDataEXT(..)
, peekDescriptorDataEXT
, EXT_DESCRIPTOR_BUFFER_SPEC_VERSION
, pattern EXT_DESCRIPTOR_BUFFER_SPEC_VERSION
, EXT_DESCRIPTOR_BUFFER_EXTENSION_NAME
, pattern EXT_DESCRIPTOR_BUFFER_EXTENSION_NAME
, AccelerationStructureKHR(..)
, AccelerationStructureNV(..)
, AccelerationStructureCreateFlagBitsKHR(..)
, AccelerationStructureCreateFlagsKHR
) 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 Foreign.Marshal.Utils (maybePeek)
import Foreign.Marshal.Utils (with)
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 Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.Trans.Cont (runContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Foreign.C.Types (CSize(..))
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.String (IsString)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(..))
import Foreign.C.Types (CSize(CSize))
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.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Extensions.Handles (AccelerationStructureKHR)
import Vulkan.Extensions.Handles (AccelerationStructureNV)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Enums.BufferUsageFlagBits (BufferUsageFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_maintenance5 (BufferUsageFlags2CreateInfoKHR)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.DescriptorSet (DescriptorImageInfo)
import Vulkan.Core10.Handles (DescriptorSetLayout)
import Vulkan.Core10.Handles (DescriptorSetLayout(..))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Core10.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkCmdBindDescriptorBufferEmbeddedSamplersEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBindDescriptorBuffersEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDescriptorBufferOffsetsEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetBufferOpaqueCaptureDescriptorDataEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetDescriptorEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetDescriptorSetLayoutBindingOffsetEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetDescriptorSetLayoutSizeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetImageOpaqueCaptureDescriptorDataEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetImageViewOpaqueCaptureDescriptorDataEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetSamplerOpaqueCaptureDescriptorDataEXT))
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.Enums.Format (Format)
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (ImageView)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..))
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Handles (Sampler)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_INPUT_ATTACHMENT))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_SAMPLED_IMAGE))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_SAMPLER))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_STORAGE_BUFFER))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_STORAGE_IMAGE))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_UNIFORM_BUFFER))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType(DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CAPTURE_DESCRIPTOR_DATA_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BUFFER_CAPTURE_DESCRIPTOR_DATA_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_ADDRESS_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_BUFFER_BINDING_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_BUFFER_BINDING_PUSH_DESCRIPTOR_BUFFER_HANDLE_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_GET_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_CAPTURE_DESCRIPTOR_DATA_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_CAPTURE_DESCRIPTOR_DATA_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_OPAQUE_CAPTURE_DESCRIPTOR_DATA_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_DENSITY_MAP_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SAMPLER_CAPTURE_DESCRIPTOR_DATA_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureCreateFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureCreateFlagsKHR)
import Vulkan.Extensions.Handles (AccelerationStructureKHR(..))
import Vulkan.Extensions.Handles (AccelerationStructureNV(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDescriptorSetLayoutSizeEXT
:: FunPtr (Ptr Device_T -> DescriptorSetLayout -> Ptr DeviceSize -> IO ()) -> Ptr Device_T -> DescriptorSetLayout -> Ptr DeviceSize -> IO ()
getDescriptorSetLayoutSizeEXT :: forall io
. (MonadIO io)
=>
Device
->
DescriptorSetLayout
-> io (("layoutSizeInBytes" ::: DeviceSize))
getDescriptorSetLayoutSizeEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> DescriptorSetLayout -> io DeviceAddress
getDescriptorSetLayoutSizeEXT Device
device DescriptorSetLayout
layout = 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 vkGetDescriptorSetLayoutSizeEXTPtr :: FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkGetDescriptorSetLayoutSizeEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
pVkGetDescriptorSetLayoutSizeEXT (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
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkGetDescriptorSetLayoutSizeEXTPtr 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 vkGetDescriptorSetLayoutSizeEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetDescriptorSetLayoutSizeEXT' :: Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
vkGetDescriptorSetLayoutSizeEXT' = FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
-> Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
mkVkGetDescriptorSetLayoutSizeEXT FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkGetDescriptorSetLayoutSizeEXTPtr
"pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPLayoutSizeInBytes <- 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 @DeviceSize Int
8) 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
"vkGetDescriptorSetLayoutSizeEXT" (Ptr Device_T
-> DescriptorSetLayout
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
vkGetDescriptorSetLayoutSizeEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(DescriptorSetLayout
layout)
("pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPLayoutSizeInBytes))
DeviceAddress
pLayoutSizeInBytes <- 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 @DeviceSize "pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPLayoutSizeInBytes
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (DeviceAddress
pLayoutSizeInBytes)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDescriptorSetLayoutBindingOffsetEXT
:: FunPtr (Ptr Device_T -> DescriptorSetLayout -> Word32 -> Ptr DeviceSize -> IO ()) -> Ptr Device_T -> DescriptorSetLayout -> Word32 -> Ptr DeviceSize -> IO ()
getDescriptorSetLayoutBindingOffsetEXT :: forall io
. (MonadIO io)
=>
Device
->
DescriptorSetLayout
->
("binding" ::: Word32)
-> io (("offset" ::: DeviceSize))
getDescriptorSetLayoutBindingOffsetEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> io DeviceAddress
getDescriptorSetLayoutBindingOffsetEXT Device
device
DescriptorSetLayout
layout
"binding" ::: Word32
binding = 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 vkGetDescriptorSetLayoutBindingOffsetEXTPtr :: FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkGetDescriptorSetLayoutBindingOffsetEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
pVkGetDescriptorSetLayoutBindingOffsetEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkGetDescriptorSetLayoutBindingOffsetEXTPtr 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 vkGetDescriptorSetLayoutBindingOffsetEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetDescriptorSetLayoutBindingOffsetEXT' :: Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
vkGetDescriptorSetLayoutBindingOffsetEXT' = FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
-> Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
mkVkGetDescriptorSetLayoutBindingOffsetEXT FunPtr
(Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkGetDescriptorSetLayoutBindingOffsetEXTPtr
"pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPOffset <- 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 @DeviceSize Int
8) 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
"vkGetDescriptorSetLayoutBindingOffsetEXT" (Ptr Device_T
-> DescriptorSetLayout
-> ("binding" ::: Word32)
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
vkGetDescriptorSetLayoutBindingOffsetEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(DescriptorSetLayout
layout)
("binding" ::: Word32
binding)
("pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPOffset))
DeviceAddress
pOffset <- 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 @DeviceSize "pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPOffset
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (DeviceAddress
pOffset)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDescriptorEXT
:: FunPtr (Ptr Device_T -> Ptr DescriptorGetInfoEXT -> CSize -> Ptr () -> IO ()) -> Ptr Device_T -> Ptr DescriptorGetInfoEXT -> CSize -> Ptr () -> IO ()
getDescriptorEXT :: forall io
. (MonadIO io)
=>
Device
->
("descriptorInfo" ::: DescriptorGetInfoEXT)
->
("dataSize" ::: Word64)
->
("descriptor" ::: Ptr ())
-> io ()
getDescriptorEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DescriptorGetInfoEXT
-> DeviceAddress
-> ("descriptor" ::: Ptr ())
-> io ()
getDescriptorEXT Device
device
DescriptorGetInfoEXT
descriptorInfo
DeviceAddress
dataSize
"descriptor" ::: Ptr ()
descriptor = 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 vkGetDescriptorEXTPtr :: FunPtr
(Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ())
vkGetDescriptorEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ())
pVkGetDescriptorEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ())
vkGetDescriptorEXTPtr 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 vkGetDescriptorEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetDescriptorEXT' :: Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ()
vkGetDescriptorEXT' = FunPtr
(Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ())
-> Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ()
mkVkGetDescriptorEXT FunPtr
(Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ())
vkGetDescriptorEXTPtr
"pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
pDescriptorInfo <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorGetInfoEXT
descriptorInfo)
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
"vkGetDescriptorEXT" (Ptr Device_T
-> ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> ("dataSize" ::: CSize)
-> ("descriptor" ::: Ptr ())
-> IO ()
vkGetDescriptorEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
pDescriptorInfo
(DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
dataSize))
("descriptor" ::: Ptr ()
descriptor))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdBindDescriptorBuffersEXT
:: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr (SomeStruct DescriptorBufferBindingInfoEXT) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr (SomeStruct DescriptorBufferBindingInfoEXT) -> IO ()
cmdBindDescriptorBuffersEXT :: forall io
. (MonadIO io)
=>
CommandBuffer
->
("bindingInfos" ::: Vector (SomeStruct DescriptorBufferBindingInfoEXT))
-> io ()
cmdBindDescriptorBuffersEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("bindingInfos"
::: Vector (SomeStruct DescriptorBufferBindingInfoEXT))
-> io ()
cmdBindDescriptorBuffersEXT CommandBuffer
commandBuffer "bindingInfos"
::: Vector (SomeStruct DescriptorBufferBindingInfoEXT)
bindingInfos = 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 vkCmdBindDescriptorBuffersEXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ())
vkCmdBindDescriptorBuffersEXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ())
pVkCmdBindDescriptorBuffersEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ())
vkCmdBindDescriptorBuffersEXTPtr 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 vkCmdBindDescriptorBuffersEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdBindDescriptorBuffersEXT' :: Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ()
vkCmdBindDescriptorBuffersEXT' = FunPtr
(Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ())
-> Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ()
mkVkCmdBindDescriptorBuffersEXT FunPtr
(Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ())
vkCmdBindDescriptorBuffersEXTPtr
Ptr (DescriptorBufferBindingInfoEXT Any)
pPBindingInfos <- 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 @(DescriptorBufferBindingInfoEXT _) ((forall a. Vector a -> Int
Data.Vector.length ("bindingInfos"
::: Vector (SomeStruct DescriptorBufferBindingInfoEXT)
bindingInfos)) forall a. Num a => a -> a -> a
* Int
32)
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i SomeStruct DescriptorBufferBindingInfoEXT
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 (DescriptorBufferBindingInfoEXT Any)
pPBindingInfos forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
32 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (DescriptorBufferBindingInfoEXT _))) (SomeStruct DescriptorBufferBindingInfoEXT
e) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) ("bindingInfos"
::: Vector (SomeStruct DescriptorBufferBindingInfoEXT)
bindingInfos)
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
"vkCmdBindDescriptorBuffersEXT" (Ptr CommandBuffer_T
-> ("binding" ::: Word32)
-> ("pBindingInfos"
::: Ptr (SomeStruct DescriptorBufferBindingInfoEXT))
-> IO ()
vkCmdBindDescriptorBuffersEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
((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
$ ("bindingInfos"
::: Vector (SomeStruct DescriptorBufferBindingInfoEXT)
bindingInfos)) :: Word32))
(forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (DescriptorBufferBindingInfoEXT Any)
pPBindingInfos)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdSetDescriptorBufferOffsetsEXT
:: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr Word32 -> Ptr DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr Word32 -> Ptr DeviceSize -> IO ()
cmdSetDescriptorBufferOffsetsEXT :: forall io
. (MonadIO io)
=>
CommandBuffer
->
PipelineBindPoint
->
PipelineLayout
->
("firstSet" ::: Word32)
->
("bufferIndices" ::: Vector Word32)
->
("offsets" ::: Vector DeviceSize)
-> io ()
cmdSetDescriptorBufferOffsetsEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("bufferIndices" ::: Vector ("binding" ::: Word32))
-> ("offsets" ::: Vector DeviceAddress)
-> io ()
cmdSetDescriptorBufferOffsetsEXT CommandBuffer
commandBuffer
PipelineBindPoint
pipelineBindPoint
PipelineLayout
layout
"binding" ::: Word32
firstSet
"bufferIndices" ::: Vector ("binding" ::: Word32)
bufferIndices
"offsets" ::: Vector DeviceAddress
offsets = 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 vkCmdSetDescriptorBufferOffsetsEXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkCmdSetDescriptorBufferOffsetsEXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
pVkCmdSetDescriptorBufferOffsetsEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkCmdSetDescriptorBufferOffsetsEXTPtr 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 vkCmdSetDescriptorBufferOffsetsEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdSetDescriptorBufferOffsetsEXT' :: Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
vkCmdSetDescriptorBufferOffsetsEXT' = FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
-> Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
mkVkCmdSetDescriptorBufferOffsetsEXT FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ())
vkCmdSetDescriptorBufferOffsetsEXTPtr
let pBufferIndicesLength :: Int
pBufferIndicesLength = forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("bufferIndices" ::: Vector ("binding" ::: Word32)
bufferIndices)
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 ((forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("offsets" ::: Vector DeviceAddress
offsets)) forall a. Eq a => a -> a -> Bool
== Int
pBufferIndicesLength) 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
"pOffsets and pBufferIndices must have the same length" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
"pBufferIndices" ::: Ptr ("binding" ::: Word32)
pPBufferIndices <- 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 @Word32 ((forall a. Vector a -> Int
Data.Vector.length ("bufferIndices" ::: Vector ("binding" ::: Word32)
bufferIndices)) forall a. Num a => a -> a -> a
* Int
4)
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 "binding" ::: Word32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pBufferIndices" ::: Ptr ("binding" ::: Word32)
pPBufferIndices forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("binding" ::: Word32
e)) ("bufferIndices" ::: Vector ("binding" ::: Word32)
bufferIndices)
"pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPOffsets <- 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 @DeviceSize ((forall a. Vector a -> Int
Data.Vector.length ("offsets" ::: Vector DeviceAddress
offsets)) 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 DeviceAddress
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPOffsets forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) (DeviceAddress
e)) ("offsets" ::: Vector DeviceAddress
offsets)
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
"vkCmdSetDescriptorBufferOffsetsEXT" (Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("pBufferIndices" ::: Ptr ("binding" ::: Word32))
-> ("pLayoutSizeInBytes" ::: Ptr DeviceAddress)
-> IO ()
vkCmdSetDescriptorBufferOffsetsEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
(PipelineBindPoint
pipelineBindPoint)
(PipelineLayout
layout)
("binding" ::: Word32
firstSet)
((forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pBufferIndicesLength :: Word32))
("pBufferIndices" ::: Ptr ("binding" ::: Word32)
pPBufferIndices)
("pLayoutSizeInBytes" ::: Ptr DeviceAddress
pPOffsets))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdBindDescriptorBufferEmbeddedSamplersEXT
:: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> IO ()
cmdBindDescriptorBufferEmbeddedSamplersEXT :: forall io
. (MonadIO io)
=>
CommandBuffer
->
PipelineBindPoint
->
PipelineLayout
->
("set" ::: Word32)
-> io ()
cmdBindDescriptorBufferEmbeddedSamplersEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> io ()
cmdBindDescriptorBufferEmbeddedSamplersEXT CommandBuffer
commandBuffer
PipelineBindPoint
pipelineBindPoint
PipelineLayout
layout
"binding" ::: Word32
set = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let vkCmdBindDescriptorBufferEmbeddedSamplersEXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ())
vkCmdBindDescriptorBufferEmbeddedSamplersEXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ())
pVkCmdBindDescriptorBufferEmbeddedSamplersEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ())
vkCmdBindDescriptorBufferEmbeddedSamplersEXTPtr 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 vkCmdBindDescriptorBufferEmbeddedSamplersEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdBindDescriptorBufferEmbeddedSamplersEXT' :: Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ()
vkCmdBindDescriptorBufferEmbeddedSamplersEXT' = FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ())
-> Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ()
mkVkCmdBindDescriptorBufferEmbeddedSamplersEXT FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ())
vkCmdBindDescriptorBufferEmbeddedSamplersEXTPtr
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdBindDescriptorBufferEmbeddedSamplersEXT" (Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("binding" ::: Word32)
-> IO ()
vkCmdBindDescriptorBufferEmbeddedSamplersEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
(PipelineBindPoint
pipelineBindPoint)
(PipelineLayout
layout)
("binding" ::: Word32
set))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetBufferOpaqueCaptureDescriptorDataEXT
:: FunPtr (Ptr Device_T -> Ptr BufferCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result) -> Ptr Device_T -> Ptr BufferCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result
getBufferOpaqueCaptureDescriptorDataEXT :: forall io
. (MonadIO io)
=>
Device
->
BufferCaptureDescriptorDataInfoEXT
->
("data" ::: Ptr ())
-> io ()
getBufferOpaqueCaptureDescriptorDataEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> BufferCaptureDescriptorDataInfoEXT
-> ("descriptor" ::: Ptr ())
-> io ()
getBufferOpaqueCaptureDescriptorDataEXT Device
device
BufferCaptureDescriptorDataInfoEXT
info
"descriptor" ::: Ptr ()
data' = 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 vkGetBufferOpaqueCaptureDescriptorDataEXTPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetBufferOpaqueCaptureDescriptorDataEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
pVkGetBufferOpaqueCaptureDescriptorDataEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetBufferOpaqueCaptureDescriptorDataEXTPtr 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 vkGetBufferOpaqueCaptureDescriptorDataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetBufferOpaqueCaptureDescriptorDataEXT' :: Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetBufferOpaqueCaptureDescriptorDataEXT' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
mkVkGetBufferOpaqueCaptureDescriptorDataEXT FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetBufferOpaqueCaptureDescriptorDataEXTPtr
"pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
pInfo <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (BufferCaptureDescriptorDataInfoEXT
info)
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
"vkGetBufferOpaqueCaptureDescriptorDataEXT" (Ptr Device_T
-> ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetBufferOpaqueCaptureDescriptorDataEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
pInfo
("descriptor" ::: Ptr ()
data'))
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))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetImageOpaqueCaptureDescriptorDataEXT
:: FunPtr (Ptr Device_T -> Ptr ImageCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result) -> Ptr Device_T -> Ptr ImageCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result
getImageOpaqueCaptureDescriptorDataEXT :: forall io
. (MonadIO io)
=>
Device
->
ImageCaptureDescriptorDataInfoEXT
->
("data" ::: Ptr ())
-> io ()
getImageOpaqueCaptureDescriptorDataEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ImageCaptureDescriptorDataInfoEXT
-> ("descriptor" ::: Ptr ())
-> io ()
getImageOpaqueCaptureDescriptorDataEXT Device
device
ImageCaptureDescriptorDataInfoEXT
info
"descriptor" ::: Ptr ()
data' = 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 vkGetImageOpaqueCaptureDescriptorDataEXTPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetImageOpaqueCaptureDescriptorDataEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
pVkGetImageOpaqueCaptureDescriptorDataEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetImageOpaqueCaptureDescriptorDataEXTPtr 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 vkGetImageOpaqueCaptureDescriptorDataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetImageOpaqueCaptureDescriptorDataEXT' :: Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetImageOpaqueCaptureDescriptorDataEXT' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
mkVkGetImageOpaqueCaptureDescriptorDataEXT FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetImageOpaqueCaptureDescriptorDataEXTPtr
"pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
pInfo <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageCaptureDescriptorDataInfoEXT
info)
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
"vkGetImageOpaqueCaptureDescriptorDataEXT" (Ptr Device_T
-> ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetImageOpaqueCaptureDescriptorDataEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
pInfo
("descriptor" ::: Ptr ()
data'))
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))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetImageViewOpaqueCaptureDescriptorDataEXT
:: FunPtr (Ptr Device_T -> Ptr ImageViewCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result) -> Ptr Device_T -> Ptr ImageViewCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result
getImageViewOpaqueCaptureDescriptorDataEXT :: forall io
. (MonadIO io)
=>
Device
->
ImageViewCaptureDescriptorDataInfoEXT
->
("data" ::: Ptr ())
-> io ()
getImageViewOpaqueCaptureDescriptorDataEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ImageViewCaptureDescriptorDataInfoEXT
-> ("descriptor" ::: Ptr ())
-> io ()
getImageViewOpaqueCaptureDescriptorDataEXT Device
device
ImageViewCaptureDescriptorDataInfoEXT
info
"descriptor" ::: Ptr ()
data' = 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 vkGetImageViewOpaqueCaptureDescriptorDataEXTPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetImageViewOpaqueCaptureDescriptorDataEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
pVkGetImageViewOpaqueCaptureDescriptorDataEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetImageViewOpaqueCaptureDescriptorDataEXTPtr 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 vkGetImageViewOpaqueCaptureDescriptorDataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetImageViewOpaqueCaptureDescriptorDataEXT' :: Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetImageViewOpaqueCaptureDescriptorDataEXT' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
mkVkGetImageViewOpaqueCaptureDescriptorDataEXT FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetImageViewOpaqueCaptureDescriptorDataEXTPtr
"pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
pInfo <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageViewCaptureDescriptorDataInfoEXT
info)
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
"vkGetImageViewOpaqueCaptureDescriptorDataEXT" (Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetImageViewOpaqueCaptureDescriptorDataEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
pInfo
("descriptor" ::: Ptr ()
data'))
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))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetSamplerOpaqueCaptureDescriptorDataEXT
:: FunPtr (Ptr Device_T -> Ptr SamplerCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result) -> Ptr Device_T -> Ptr SamplerCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result
getSamplerOpaqueCaptureDescriptorDataEXT :: forall io
. (MonadIO io)
=>
Device
->
SamplerCaptureDescriptorDataInfoEXT
->
("data" ::: Ptr ())
-> io ()
getSamplerOpaqueCaptureDescriptorDataEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> SamplerCaptureDescriptorDataInfoEXT
-> ("descriptor" ::: Ptr ())
-> io ()
getSamplerOpaqueCaptureDescriptorDataEXT Device
device
SamplerCaptureDescriptorDataInfoEXT
info
"descriptor" ::: Ptr ()
data' = 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 vkGetSamplerOpaqueCaptureDescriptorDataEXTPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetSamplerOpaqueCaptureDescriptorDataEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
pVkGetSamplerOpaqueCaptureDescriptorDataEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetSamplerOpaqueCaptureDescriptorDataEXTPtr 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 vkGetSamplerOpaqueCaptureDescriptorDataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetSamplerOpaqueCaptureDescriptorDataEXT' :: Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetSamplerOpaqueCaptureDescriptorDataEXT' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
mkVkGetSamplerOpaqueCaptureDescriptorDataEXT FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetSamplerOpaqueCaptureDescriptorDataEXTPtr
"pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
pInfo <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (SamplerCaptureDescriptorDataInfoEXT
info)
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
"vkGetSamplerOpaqueCaptureDescriptorDataEXT" (Ptr Device_T
-> ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetSamplerOpaqueCaptureDescriptorDataEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
pInfo
("descriptor" ::: Ptr ()
data'))
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))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT
:: FunPtr (Ptr Device_T -> Ptr AccelerationStructureCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result) -> Ptr Device_T -> Ptr AccelerationStructureCaptureDescriptorDataInfoEXT -> Ptr () -> IO Result
getAccelerationStructureOpaqueCaptureDescriptorDataEXT :: forall io
. (MonadIO io)
=>
Device
->
AccelerationStructureCaptureDescriptorDataInfoEXT
->
("data" ::: Ptr ())
-> io ()
getAccelerationStructureOpaqueCaptureDescriptorDataEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> AccelerationStructureCaptureDescriptorDataInfoEXT
-> ("descriptor" ::: Ptr ())
-> io ()
getAccelerationStructureOpaqueCaptureDescriptorDataEXT Device
device
AccelerationStructureCaptureDescriptorDataInfoEXT
info
"descriptor" ::: Ptr ()
data' = 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 vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXTPtr :: FunPtr
(Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
pVkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXTPtr 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 vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT' :: Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT' = FunPtr
(Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
-> Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
mkVkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT FunPtr
(Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result)
vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXTPtr
"pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
pInfo <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureCaptureDescriptorDataInfoEXT
info)
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
"vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT" (Ptr Device_T
-> ("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> ("descriptor" ::: Ptr ())
-> IO Result
vkGetAccelerationStructureOpaqueCaptureDescriptorDataEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
pInfo
("descriptor" ::: Ptr ()
data'))
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 PhysicalDeviceDescriptorBufferFeaturesEXT = PhysicalDeviceDescriptorBufferFeaturesEXT
{
PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
descriptorBuffer :: Bool
,
PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
descriptorBufferCaptureReplay :: Bool
,
PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
descriptorBufferImageLayoutIgnored :: Bool
,
PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
descriptorBufferPushDescriptors :: Bool
}
deriving (Typeable, PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
$c/= :: PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
== :: PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
$c== :: PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDescriptorBufferFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceDescriptorBufferFeaturesEXT
instance ToCStruct PhysicalDeviceDescriptorBufferFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceDescriptorBufferFeaturesEXT
-> (Ptr PhysicalDeviceDescriptorBufferFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceDescriptorBufferFeaturesEXT
x Ptr PhysicalDeviceDescriptorBufferFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p PhysicalDeviceDescriptorBufferFeaturesEXT
x (Ptr PhysicalDeviceDescriptorBufferFeaturesEXT -> IO b
f Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p PhysicalDeviceDescriptorBufferFeaturesEXT{Bool
descriptorBufferPushDescriptors :: Bool
descriptorBufferImageLayoutIgnored :: Bool
descriptorBufferCaptureReplay :: Bool
descriptorBuffer :: Bool
$sel:descriptorBufferPushDescriptors:PhysicalDeviceDescriptorBufferFeaturesEXT :: PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
$sel:descriptorBufferImageLayoutIgnored:PhysicalDeviceDescriptorBufferFeaturesEXT :: PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
$sel:descriptorBufferCaptureReplay:PhysicalDeviceDescriptorBufferFeaturesEXT :: PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
$sel:descriptorBuffer:PhysicalDeviceDescriptorBufferFeaturesEXT :: PhysicalDeviceDescriptorBufferFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBuffer))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBufferCaptureReplay))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBufferImageLayoutIgnored))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBufferPushDescriptors))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDescriptorBufferFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceDescriptorBufferFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
-> IO PhysicalDeviceDescriptorBufferFeaturesEXT
peekCStruct Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p = do
Bool32
descriptorBuffer <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
descriptorBufferCaptureReplay <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
descriptorBufferImageLayoutIgnored <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
descriptorBufferPushDescriptors <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceDescriptorBufferFeaturesEXT
PhysicalDeviceDescriptorBufferFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBuffer)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBufferCaptureReplay)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBufferImageLayoutIgnored)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBufferPushDescriptors)
instance Storable PhysicalDeviceDescriptorBufferFeaturesEXT where
sizeOf :: PhysicalDeviceDescriptorBufferFeaturesEXT -> Int
sizeOf ~PhysicalDeviceDescriptorBufferFeaturesEXT
_ = Int
32
alignment :: PhysicalDeviceDescriptorBufferFeaturesEXT -> Int
alignment ~PhysicalDeviceDescriptorBufferFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
-> IO PhysicalDeviceDescriptorBufferFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
-> PhysicalDeviceDescriptorBufferFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
ptr PhysicalDeviceDescriptorBufferFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferFeaturesEXT
ptr PhysicalDeviceDescriptorBufferFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDescriptorBufferFeaturesEXT where
zero :: PhysicalDeviceDescriptorBufferFeaturesEXT
zero = Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceDescriptorBufferFeaturesEXT
PhysicalDeviceDescriptorBufferFeaturesEXT
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 PhysicalDeviceDescriptorBufferPropertiesEXT = PhysicalDeviceDescriptorBufferPropertiesEXT
{
PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
combinedImageSamplerDescriptorSingleArray :: Bool
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
bufferlessPushDescriptors :: Bool
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
allowSamplerImageViewPostSubmitCreation :: Bool
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
descriptorBufferOffsetAlignment :: DeviceSize
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
maxDescriptorBufferBindings :: Word32
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
maxResourceDescriptorBufferBindings :: Word32
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
maxSamplerDescriptorBufferBindings :: Word32
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
maxEmbeddedImmutableSamplerBindings :: Word32
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
maxEmbeddedImmutableSamplers :: Word32
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
bufferCaptureReplayDescriptorDataSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
imageCaptureReplayDescriptorDataSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
imageViewCaptureReplayDescriptorDataSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
samplerCaptureReplayDescriptorDataSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
accelerationStructureCaptureReplayDescriptorDataSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
samplerDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
combinedImageSamplerDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
sampledImageDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
storageImageDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
uniformTexelBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
robustUniformTexelBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
storageTexelBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
robustStorageTexelBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
uniformBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
robustUniformBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
storageBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
robustStorageBufferDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
inputAttachmentDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
accelerationStructureDescriptorSize :: Word64
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
maxSamplerDescriptorBufferRange :: DeviceSize
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
maxResourceDescriptorBufferRange :: DeviceSize
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
samplerDescriptorBufferAddressSpaceSize :: DeviceSize
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
resourceDescriptorBufferAddressSpaceSize :: DeviceSize
,
PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
descriptorBufferAddressSpaceSize :: DeviceSize
}
deriving (Typeable, PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
$c/= :: PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
== :: PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
$c== :: PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDescriptorBufferPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceDescriptorBufferPropertiesEXT
instance ToCStruct PhysicalDeviceDescriptorBufferPropertiesEXT where
withCStruct :: forall b.
PhysicalDeviceDescriptorBufferPropertiesEXT
-> (Ptr PhysicalDeviceDescriptorBufferPropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceDescriptorBufferPropertiesEXT
x Ptr PhysicalDeviceDescriptorBufferPropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
256 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p PhysicalDeviceDescriptorBufferPropertiesEXT
x (Ptr PhysicalDeviceDescriptorBufferPropertiesEXT -> IO b
f Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p PhysicalDeviceDescriptorBufferPropertiesEXT{Bool
"binding" ::: Word32
DeviceAddress
descriptorBufferAddressSpaceSize :: DeviceAddress
resourceDescriptorBufferAddressSpaceSize :: DeviceAddress
samplerDescriptorBufferAddressSpaceSize :: DeviceAddress
maxResourceDescriptorBufferRange :: DeviceAddress
maxSamplerDescriptorBufferRange :: DeviceAddress
accelerationStructureDescriptorSize :: DeviceAddress
inputAttachmentDescriptorSize :: DeviceAddress
robustStorageBufferDescriptorSize :: DeviceAddress
storageBufferDescriptorSize :: DeviceAddress
robustUniformBufferDescriptorSize :: DeviceAddress
uniformBufferDescriptorSize :: DeviceAddress
robustStorageTexelBufferDescriptorSize :: DeviceAddress
storageTexelBufferDescriptorSize :: DeviceAddress
robustUniformTexelBufferDescriptorSize :: DeviceAddress
uniformTexelBufferDescriptorSize :: DeviceAddress
storageImageDescriptorSize :: DeviceAddress
sampledImageDescriptorSize :: DeviceAddress
combinedImageSamplerDescriptorSize :: DeviceAddress
samplerDescriptorSize :: DeviceAddress
accelerationStructureCaptureReplayDescriptorDataSize :: DeviceAddress
samplerCaptureReplayDescriptorDataSize :: DeviceAddress
imageViewCaptureReplayDescriptorDataSize :: DeviceAddress
imageCaptureReplayDescriptorDataSize :: DeviceAddress
bufferCaptureReplayDescriptorDataSize :: DeviceAddress
maxEmbeddedImmutableSamplers :: "binding" ::: Word32
maxEmbeddedImmutableSamplerBindings :: "binding" ::: Word32
maxSamplerDescriptorBufferBindings :: "binding" ::: Word32
maxResourceDescriptorBufferBindings :: "binding" ::: Word32
maxDescriptorBufferBindings :: "binding" ::: Word32
descriptorBufferOffsetAlignment :: DeviceAddress
allowSamplerImageViewPostSubmitCreation :: Bool
bufferlessPushDescriptors :: Bool
combinedImageSamplerDescriptorSingleArray :: Bool
$sel:descriptorBufferAddressSpaceSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:resourceDescriptorBufferAddressSpaceSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:samplerDescriptorBufferAddressSpaceSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:maxResourceDescriptorBufferRange:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:maxSamplerDescriptorBufferRange:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:accelerationStructureDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:inputAttachmentDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:robustStorageBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:storageBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:robustUniformBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:uniformBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:robustStorageTexelBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:storageTexelBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:robustUniformTexelBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:uniformTexelBufferDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:storageImageDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:sampledImageDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:combinedImageSamplerDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:samplerDescriptorSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:accelerationStructureCaptureReplayDescriptorDataSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:samplerCaptureReplayDescriptorDataSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:imageViewCaptureReplayDescriptorDataSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:imageCaptureReplayDescriptorDataSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:bufferCaptureReplayDescriptorDataSize:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:maxEmbeddedImmutableSamplers:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
$sel:maxEmbeddedImmutableSamplerBindings:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
$sel:maxSamplerDescriptorBufferBindings:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
$sel:maxResourceDescriptorBufferBindings:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
$sel:maxDescriptorBufferBindings:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> "binding" ::: Word32
$sel:descriptorBufferOffsetAlignment:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> DeviceAddress
$sel:allowSamplerImageViewPostSubmitCreation:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
$sel:bufferlessPushDescriptors:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
$sel:combinedImageSamplerDescriptorSingleArray:PhysicalDeviceDescriptorBufferPropertiesEXT :: PhysicalDeviceDescriptorBufferPropertiesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
combinedImageSamplerDescriptorSingleArray))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferlessPushDescriptors))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
allowSamplerImageViewPostSubmitCreation))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (DeviceAddress
descriptorBufferOffsetAlignment)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) ("binding" ::: Word32
maxDescriptorBufferBindings)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32)) ("binding" ::: Word32
maxResourceDescriptorBufferBindings)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32)) ("binding" ::: Word32
maxSamplerDescriptorBufferBindings)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32)) ("binding" ::: Word32
maxEmbeddedImmutableSamplerBindings)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) ("binding" ::: Word32
maxEmbeddedImmutableSamplers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
bufferCaptureReplayDescriptorDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
imageCaptureReplayDescriptorDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
imageViewCaptureReplayDescriptorDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
samplerCaptureReplayDescriptorDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
accelerationStructureCaptureReplayDescriptorDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
samplerDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
combinedImageSamplerDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
sampledImageDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
storageImageDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
uniformTexelBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
robustUniformTexelBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
storageTexelBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
robustStorageTexelBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
uniformBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
robustUniformBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
storageBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
robustStorageBufferDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
inputAttachmentDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
208 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
accelerationStructureDescriptorSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
216 :: Ptr DeviceSize)) (DeviceAddress
maxSamplerDescriptorBufferRange)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
224 :: Ptr DeviceSize)) (DeviceAddress
maxResourceDescriptorBufferRange)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
232 :: Ptr DeviceSize)) (DeviceAddress
samplerDescriptorBufferAddressSpaceSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
240 :: Ptr DeviceSize)) (DeviceAddress
resourceDescriptorBufferAddressSpaceSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
248 :: Ptr DeviceSize)) (DeviceAddress
descriptorBufferAddressSpaceSize)
IO b
f
cStructSize :: Int
cStructSize = Int
256
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDescriptorBufferPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
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 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
208 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
216 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
224 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
232 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
240 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
248 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceDescriptorBufferPropertiesEXT where
peekCStruct :: Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
-> IO PhysicalDeviceDescriptorBufferPropertiesEXT
peekCStruct Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p = do
Bool32
combinedImageSamplerDescriptorSingleArray <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
bufferlessPushDescriptors <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
allowSamplerImageViewPostSubmitCreation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
DeviceAddress
descriptorBufferOffsetAlignment <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize))
"binding" ::: Word32
maxDescriptorBufferBindings <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32))
"binding" ::: Word32
maxResourceDescriptorBufferBindings <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32))
"binding" ::: Word32
maxSamplerDescriptorBufferBindings <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32))
"binding" ::: Word32
maxEmbeddedImmutableSamplerBindings <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32))
"binding" ::: Word32
maxEmbeddedImmutableSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32))
"dataSize" ::: CSize
bufferCaptureReplayDescriptorDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr CSize))
"dataSize" ::: CSize
imageCaptureReplayDescriptorDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr CSize))
"dataSize" ::: CSize
imageViewCaptureReplayDescriptorDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr CSize))
"dataSize" ::: CSize
samplerCaptureReplayDescriptorDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr CSize))
"dataSize" ::: CSize
accelerationStructureCaptureReplayDescriptorDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr CSize))
"dataSize" ::: CSize
samplerDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr CSize))
"dataSize" ::: CSize
combinedImageSamplerDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr CSize))
"dataSize" ::: CSize
sampledImageDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr CSize))
"dataSize" ::: CSize
storageImageDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr CSize))
"dataSize" ::: CSize
uniformTexelBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr CSize))
"dataSize" ::: CSize
robustUniformTexelBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr CSize))
"dataSize" ::: CSize
storageTexelBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr CSize))
"dataSize" ::: CSize
robustStorageTexelBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr CSize))
"dataSize" ::: CSize
uniformBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr CSize))
"dataSize" ::: CSize
robustUniformBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr CSize))
"dataSize" ::: CSize
storageBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr CSize))
"dataSize" ::: CSize
robustStorageBufferDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr CSize))
"dataSize" ::: CSize
inputAttachmentDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr CSize))
"dataSize" ::: CSize
accelerationStructureDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
208 :: Ptr CSize))
DeviceAddress
maxSamplerDescriptorBufferRange <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
216 :: Ptr DeviceSize))
DeviceAddress
maxResourceDescriptorBufferRange <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
224 :: Ptr DeviceSize))
DeviceAddress
samplerDescriptorBufferAddressSpaceSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
232 :: Ptr DeviceSize))
DeviceAddress
resourceDescriptorBufferAddressSpaceSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
240 :: Ptr DeviceSize))
DeviceAddress
descriptorBufferAddressSpaceSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
248 :: Ptr DeviceSize))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> DeviceAddress
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> PhysicalDeviceDescriptorBufferPropertiesEXT
PhysicalDeviceDescriptorBufferPropertiesEXT
(Bool32 -> Bool
bool32ToBool Bool32
combinedImageSamplerDescriptorSingleArray)
(Bool32 -> Bool
bool32ToBool Bool32
bufferlessPushDescriptors)
(Bool32 -> Bool
bool32ToBool Bool32
allowSamplerImageViewPostSubmitCreation)
DeviceAddress
descriptorBufferOffsetAlignment
"binding" ::: Word32
maxDescriptorBufferBindings
"binding" ::: Word32
maxResourceDescriptorBufferBindings
"binding" ::: Word32
maxSamplerDescriptorBufferBindings
"binding" ::: Word32
maxEmbeddedImmutableSamplerBindings
"binding" ::: Word32
maxEmbeddedImmutableSamplers
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
bufferCaptureReplayDescriptorDataSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
imageCaptureReplayDescriptorDataSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
imageViewCaptureReplayDescriptorDataSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
samplerCaptureReplayDescriptorDataSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
accelerationStructureCaptureReplayDescriptorDataSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
samplerDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
combinedImageSamplerDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
sampledImageDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
storageImageDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
uniformTexelBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
robustUniformTexelBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
storageTexelBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
robustStorageTexelBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
uniformBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
robustUniformBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
storageBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
robustStorageBufferDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
inputAttachmentDescriptorSize)
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
accelerationStructureDescriptorSize)
DeviceAddress
maxSamplerDescriptorBufferRange
DeviceAddress
maxResourceDescriptorBufferRange
DeviceAddress
samplerDescriptorBufferAddressSpaceSize
DeviceAddress
resourceDescriptorBufferAddressSpaceSize
DeviceAddress
descriptorBufferAddressSpaceSize
instance Storable PhysicalDeviceDescriptorBufferPropertiesEXT where
sizeOf :: PhysicalDeviceDescriptorBufferPropertiesEXT -> Int
sizeOf ~PhysicalDeviceDescriptorBufferPropertiesEXT
_ = Int
256
alignment :: PhysicalDeviceDescriptorBufferPropertiesEXT -> Int
alignment ~PhysicalDeviceDescriptorBufferPropertiesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
-> IO PhysicalDeviceDescriptorBufferPropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
-> PhysicalDeviceDescriptorBufferPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
ptr PhysicalDeviceDescriptorBufferPropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferPropertiesEXT
ptr PhysicalDeviceDescriptorBufferPropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDescriptorBufferPropertiesEXT where
zero :: PhysicalDeviceDescriptorBufferPropertiesEXT
zero = Bool
-> Bool
-> Bool
-> DeviceAddress
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> ("binding" ::: Word32)
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> PhysicalDeviceDescriptorBufferPropertiesEXT
PhysicalDeviceDescriptorBufferPropertiesEXT
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
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
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
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
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
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT = PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
{
PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> DeviceAddress
combinedImageSamplerDensityMapDescriptorSize :: Word64 }
deriving (Typeable, PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Bool
$c/= :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Bool
== :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Bool
$c== :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
instance ToCStruct PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT where
withCStruct :: forall b.
PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> (Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> IO b)
-> IO b
withCStruct PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
x Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
x (Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> IO b
f Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT{DeviceAddress
combinedImageSamplerDensityMapDescriptorSize :: DeviceAddress
$sel:combinedImageSamplerDensityMapDescriptorSize:PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> DeviceAddress
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_DENSITY_MAP_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (DeviceAddress
combinedImageSamplerDensityMapDescriptorSize))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_BUFFER_DENSITY_MAP_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CSize)) (DeviceAddress -> "dataSize" ::: CSize
CSize (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT where
peekCStruct :: Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> IO PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
peekCStruct Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p = do
"dataSize" ::: CSize
combinedImageSamplerDensityMapDescriptorSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CSize))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceAddress
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
(coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 "dataSize" ::: CSize
combinedImageSamplerDensityMapDescriptorSize)
instance Storable PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT where
sizeOf :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Int
sizeOf ~PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
_ = Int
24
alignment :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> Int
alignment ~PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> IO PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
ptr PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT where
zero :: PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
zero = DeviceAddress
-> PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
PhysicalDeviceDescriptorBufferDensityMapPropertiesEXT
forall a. Zero a => a
zero
data DescriptorAddressInfoEXT = DescriptorAddressInfoEXT
{
DescriptorAddressInfoEXT -> DeviceAddress
address :: DeviceAddress
,
DescriptorAddressInfoEXT -> DeviceAddress
range :: DeviceSize
,
DescriptorAddressInfoEXT -> Format
format :: Format
}
deriving (Typeable, DescriptorAddressInfoEXT -> DescriptorAddressInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorAddressInfoEXT -> DescriptorAddressInfoEXT -> Bool
$c/= :: DescriptorAddressInfoEXT -> DescriptorAddressInfoEXT -> Bool
== :: DescriptorAddressInfoEXT -> DescriptorAddressInfoEXT -> Bool
$c== :: DescriptorAddressInfoEXT -> DescriptorAddressInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorAddressInfoEXT)
#endif
deriving instance Show DescriptorAddressInfoEXT
instance ToCStruct DescriptorAddressInfoEXT where
withCStruct :: forall b.
DescriptorAddressInfoEXT
-> (Ptr DescriptorAddressInfoEXT -> IO b) -> IO b
withCStruct DescriptorAddressInfoEXT
x Ptr DescriptorAddressInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr DescriptorAddressInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorAddressInfoEXT
p DescriptorAddressInfoEXT
x (Ptr DescriptorAddressInfoEXT -> IO b
f Ptr DescriptorAddressInfoEXT
p)
pokeCStruct :: forall b.
Ptr DescriptorAddressInfoEXT
-> DescriptorAddressInfoEXT -> IO b -> IO b
pokeCStruct Ptr DescriptorAddressInfoEXT
p DescriptorAddressInfoEXT{DeviceAddress
Format
format :: Format
range :: DeviceAddress
address :: DeviceAddress
$sel:format:DescriptorAddressInfoEXT :: DescriptorAddressInfoEXT -> Format
$sel:range:DescriptorAddressInfoEXT :: DescriptorAddressInfoEXT -> DeviceAddress
$sel:address:DescriptorAddressInfoEXT :: DescriptorAddressInfoEXT -> DeviceAddress
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_ADDRESS_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (DeviceAddress
address)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceAddress
range)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Format)) (Format
format)
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DescriptorAddressInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr DescriptorAddressInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_ADDRESS_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorAddressInfoEXT
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 ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Format)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DescriptorAddressInfoEXT where
peekCStruct :: Ptr DescriptorAddressInfoEXT -> IO DescriptorAddressInfoEXT
peekCStruct Ptr DescriptorAddressInfoEXT
p = do
DeviceAddress
address <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress))
DeviceAddress
range <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
Format
format <- forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr DescriptorAddressInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Format))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceAddress
-> DeviceAddress -> Format -> DescriptorAddressInfoEXT
DescriptorAddressInfoEXT
DeviceAddress
address DeviceAddress
range Format
format
instance Storable DescriptorAddressInfoEXT where
sizeOf :: DescriptorAddressInfoEXT -> Int
sizeOf ~DescriptorAddressInfoEXT
_ = Int
40
alignment :: DescriptorAddressInfoEXT -> Int
alignment ~DescriptorAddressInfoEXT
_ = Int
8
peek :: Ptr DescriptorAddressInfoEXT -> IO DescriptorAddressInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DescriptorAddressInfoEXT -> DescriptorAddressInfoEXT -> IO ()
poke Ptr DescriptorAddressInfoEXT
ptr DescriptorAddressInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorAddressInfoEXT
ptr DescriptorAddressInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DescriptorAddressInfoEXT where
zero :: DescriptorAddressInfoEXT
zero = DeviceAddress
-> DeviceAddress -> Format -> DescriptorAddressInfoEXT
DescriptorAddressInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data DescriptorBufferBindingInfoEXT (es :: [Type]) = DescriptorBufferBindingInfoEXT
{
forall (es :: [*]). DescriptorBufferBindingInfoEXT es -> Chain es
next :: Chain es
,
forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> DeviceAddress
address :: DeviceAddress
,
forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> BufferUsageFlags
usage :: BufferUsageFlags
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorBufferBindingInfoEXT (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (DescriptorBufferBindingInfoEXT es)
instance Extensible DescriptorBufferBindingInfoEXT where
extensibleTypeName :: String
extensibleTypeName = String
"DescriptorBufferBindingInfoEXT"
setNext :: forall (ds :: [*]) (es :: [*]).
DescriptorBufferBindingInfoEXT ds
-> Chain es -> DescriptorBufferBindingInfoEXT es
setNext DescriptorBufferBindingInfoEXT{DeviceAddress
Chain ds
BufferUsageFlags
usage :: BufferUsageFlags
address :: DeviceAddress
next :: Chain ds
$sel:usage:DescriptorBufferBindingInfoEXT :: forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> BufferUsageFlags
$sel:address:DescriptorBufferBindingInfoEXT :: forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> DeviceAddress
$sel:next:DescriptorBufferBindingInfoEXT :: forall (es :: [*]). DescriptorBufferBindingInfoEXT es -> Chain es
..} Chain es
next' = DescriptorBufferBindingInfoEXT{$sel:next:DescriptorBufferBindingInfoEXT :: Chain es
next = Chain es
next', DeviceAddress
BufferUsageFlags
usage :: BufferUsageFlags
address :: DeviceAddress
$sel:usage:DescriptorBufferBindingInfoEXT :: BufferUsageFlags
$sel:address:DescriptorBufferBindingInfoEXT :: DeviceAddress
..}
getNext :: forall (es :: [*]). DescriptorBufferBindingInfoEXT es -> Chain es
getNext DescriptorBufferBindingInfoEXT{DeviceAddress
Chain es
BufferUsageFlags
usage :: BufferUsageFlags
address :: DeviceAddress
next :: Chain es
$sel:usage:DescriptorBufferBindingInfoEXT :: forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> BufferUsageFlags
$sel:address:DescriptorBufferBindingInfoEXT :: forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> DeviceAddress
$sel:next:DescriptorBufferBindingInfoEXT :: forall (es :: [*]). DescriptorBufferBindingInfoEXT es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends DescriptorBufferBindingInfoEXT e => b) -> Maybe b
extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e
-> (Extends DescriptorBufferBindingInfoEXT e => b) -> Maybe b
extends proxy e
_ Extends DescriptorBufferBindingInfoEXT e => b
f
| Just e :~: DescriptorBufferBindingPushDescriptorBufferHandleEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DescriptorBufferBindingPushDescriptorBufferHandleEXT = forall a. a -> Maybe a
Just Extends DescriptorBufferBindingInfoEXT e => b
f
| Just e :~: BufferUsageFlags2CreateInfoKHR
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @BufferUsageFlags2CreateInfoKHR = forall a. a -> Maybe a
Just Extends DescriptorBufferBindingInfoEXT e => b
f
| Bool
otherwise = forall a. Maybe a
Nothing
instance ( Extendss DescriptorBufferBindingInfoEXT es
, PokeChain es ) => ToCStruct (DescriptorBufferBindingInfoEXT es) where
withCStruct :: forall b.
DescriptorBufferBindingInfoEXT es
-> (Ptr (DescriptorBufferBindingInfoEXT es) -> IO b) -> IO b
withCStruct DescriptorBufferBindingInfoEXT es
x Ptr (DescriptorBufferBindingInfoEXT es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr (DescriptorBufferBindingInfoEXT es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (DescriptorBufferBindingInfoEXT es)
p DescriptorBufferBindingInfoEXT es
x (Ptr (DescriptorBufferBindingInfoEXT es) -> IO b
f Ptr (DescriptorBufferBindingInfoEXT es)
p)
pokeCStruct :: forall b.
Ptr (DescriptorBufferBindingInfoEXT es)
-> DescriptorBufferBindingInfoEXT es -> IO b -> IO b
pokeCStruct Ptr (DescriptorBufferBindingInfoEXT es)
p DescriptorBufferBindingInfoEXT{DeviceAddress
Chain es
BufferUsageFlags
usage :: BufferUsageFlags
address :: DeviceAddress
next :: Chain es
$sel:usage:DescriptorBufferBindingInfoEXT :: forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> BufferUsageFlags
$sel:address:DescriptorBufferBindingInfoEXT :: forall (es :: [*]).
DescriptorBufferBindingInfoEXT es -> DeviceAddress
$sel:next:DescriptorBufferBindingInfoEXT :: forall (es :: [*]). DescriptorBufferBindingInfoEXT 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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_BUFFER_BINDING_INFO_EXT)
"descriptor" ::: 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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) "descriptor" ::: 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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (DeviceAddress
address)
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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BufferUsageFlags)) (BufferUsageFlags
usage)
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
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr (DescriptorBufferBindingInfoEXT es) -> IO b -> IO b
pokeZeroCStruct Ptr (DescriptorBufferBindingInfoEXT 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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_BUFFER_BINDING_INFO_EXT)
"descriptor" ::: 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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) "descriptor" ::: 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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (forall a. Zero a => a
zero)
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 (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BufferUsageFlags)) (forall a. Zero a => a
zero)
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 DescriptorBufferBindingInfoEXT es
, PeekChain es ) => FromCStruct (DescriptorBufferBindingInfoEXT es) where
peekCStruct :: Ptr (DescriptorBufferBindingInfoEXT es)
-> IO (DescriptorBufferBindingInfoEXT es)
peekCStruct Ptr (DescriptorBufferBindingInfoEXT es)
p = do
"descriptor" ::: Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (DescriptorBufferBindingInfoEXT 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 "descriptor" ::: Ptr ()
pNext)
DeviceAddress
address <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress))
BufferUsageFlags
usage <- forall a. Storable a => Ptr a -> IO a
peek @BufferUsageFlags ((Ptr (DescriptorBufferBindingInfoEXT es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BufferUsageFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es
-> DeviceAddress
-> BufferUsageFlags
-> DescriptorBufferBindingInfoEXT es
DescriptorBufferBindingInfoEXT
Chain es
next DeviceAddress
address BufferUsageFlags
usage
instance es ~ '[] => Zero (DescriptorBufferBindingInfoEXT es) where
zero :: DescriptorBufferBindingInfoEXT es
zero = forall (es :: [*]).
Chain es
-> DeviceAddress
-> BufferUsageFlags
-> DescriptorBufferBindingInfoEXT es
DescriptorBufferBindingInfoEXT
()
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data DescriptorBufferBindingPushDescriptorBufferHandleEXT = DescriptorBufferBindingPushDescriptorBufferHandleEXT
{
DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Buffer
buffer :: Buffer }
deriving (Typeable, DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Bool
$c/= :: DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Bool
== :: DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Bool
$c== :: DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorBufferBindingPushDescriptorBufferHandleEXT)
#endif
deriving instance Show DescriptorBufferBindingPushDescriptorBufferHandleEXT
instance ToCStruct DescriptorBufferBindingPushDescriptorBufferHandleEXT where
withCStruct :: forall b.
DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> (Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> IO b)
-> IO b
withCStruct DescriptorBufferBindingPushDescriptorBufferHandleEXT
x Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p DescriptorBufferBindingPushDescriptorBufferHandleEXT
x (Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT -> IO b
f Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p)
pokeCStruct :: forall b.
Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> IO b
-> IO b
pokeCStruct Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p DescriptorBufferBindingPushDescriptorBufferHandleEXT{Buffer
buffer :: Buffer
$sel:buffer:DescriptorBufferBindingPushDescriptorBufferHandleEXT :: DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Buffer
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_BUFFER_BINDING_PUSH_DESCRIPTOR_BUFFER_HANDLE_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (Buffer
buffer)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> IO b -> IO b
pokeZeroCStruct Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_BUFFER_BINDING_PUSH_DESCRIPTOR_BUFFER_HANDLE_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DescriptorBufferBindingPushDescriptorBufferHandleEXT where
peekCStruct :: Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> IO DescriptorBufferBindingPushDescriptorBufferHandleEXT
peekCStruct Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p = do
Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Buffer -> DescriptorBufferBindingPushDescriptorBufferHandleEXT
DescriptorBufferBindingPushDescriptorBufferHandleEXT
Buffer
buffer
instance Storable DescriptorBufferBindingPushDescriptorBufferHandleEXT where
sizeOf :: DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Int
sizeOf ~DescriptorBufferBindingPushDescriptorBufferHandleEXT
_ = Int
24
alignment :: DescriptorBufferBindingPushDescriptorBufferHandleEXT -> Int
alignment ~DescriptorBufferBindingPushDescriptorBufferHandleEXT
_ = Int
8
peek :: Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> IO DescriptorBufferBindingPushDescriptorBufferHandleEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
-> DescriptorBufferBindingPushDescriptorBufferHandleEXT -> IO ()
poke Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
ptr DescriptorBufferBindingPushDescriptorBufferHandleEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DescriptorBufferBindingPushDescriptorBufferHandleEXT where
zero :: DescriptorBufferBindingPushDescriptorBufferHandleEXT
zero = Buffer -> DescriptorBufferBindingPushDescriptorBufferHandleEXT
DescriptorBufferBindingPushDescriptorBufferHandleEXT
forall a. Zero a => a
zero
data DescriptorGetInfoEXT = DescriptorGetInfoEXT
{
DescriptorGetInfoEXT -> DescriptorType
type' :: DescriptorType
,
DescriptorGetInfoEXT -> DescriptorDataEXT
data' :: DescriptorDataEXT
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorGetInfoEXT)
#endif
deriving instance Show DescriptorGetInfoEXT
instance ToCStruct DescriptorGetInfoEXT where
withCStruct :: forall b.
DescriptorGetInfoEXT
-> (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT) -> IO b)
-> IO b
withCStruct DescriptorGetInfoEXT
x ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p DescriptorGetInfoEXT
x (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT) -> IO b
f "pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p)
pokeCStruct :: forall b.
("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> DescriptorGetInfoEXT -> IO b -> IO b
pokeCStruct "pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p DescriptorGetInfoEXT{DescriptorType
DescriptorDataEXT
data' :: DescriptorDataEXT
type' :: DescriptorType
$sel:data':DescriptorGetInfoEXT :: DescriptorGetInfoEXT -> DescriptorDataEXT
$sel:type':DescriptorGetInfoEXT :: DescriptorGetInfoEXT -> DescriptorType
..} 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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_GET_INFO_EXT)
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DescriptorType)) (DescriptorType
type')
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DescriptorDataEXT)) (DescriptorDataEXT
data') forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
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
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_GET_INFO_EXT)
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DescriptorType)) (forall a. Zero a => a
zero)
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 (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DescriptorDataEXT)) (forall a. Zero a => a
zero) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
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 FromCStruct DescriptorGetInfoEXT where
peekCStruct :: ("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT)
-> IO DescriptorGetInfoEXT
peekCStruct "pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p = do
DescriptorType
type' <- forall a. Storable a => Ptr a -> IO a
peek @DescriptorType (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DescriptorType))
DescriptorDataEXT
data' <- DescriptorType -> Ptr DescriptorDataEXT -> IO DescriptorDataEXT
peekDescriptorDataEXT DescriptorType
type' (("pDescriptorInfo" ::: Ptr DescriptorGetInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DescriptorDataEXT))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DescriptorType -> DescriptorDataEXT -> DescriptorGetInfoEXT
DescriptorGetInfoEXT
DescriptorType
type' DescriptorDataEXT
data'
instance Zero DescriptorGetInfoEXT where
zero :: DescriptorGetInfoEXT
zero = DescriptorType -> DescriptorDataEXT -> DescriptorGetInfoEXT
DescriptorGetInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data BufferCaptureDescriptorDataInfoEXT = BufferCaptureDescriptorDataInfoEXT
{
BufferCaptureDescriptorDataInfoEXT -> Buffer
buffer :: Buffer }
deriving (Typeable, BufferCaptureDescriptorDataInfoEXT
-> BufferCaptureDescriptorDataInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferCaptureDescriptorDataInfoEXT
-> BufferCaptureDescriptorDataInfoEXT -> Bool
$c/= :: BufferCaptureDescriptorDataInfoEXT
-> BufferCaptureDescriptorDataInfoEXT -> Bool
== :: BufferCaptureDescriptorDataInfoEXT
-> BufferCaptureDescriptorDataInfoEXT -> Bool
$c== :: BufferCaptureDescriptorDataInfoEXT
-> BufferCaptureDescriptorDataInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferCaptureDescriptorDataInfoEXT)
#endif
deriving instance Show BufferCaptureDescriptorDataInfoEXT
instance ToCStruct BufferCaptureDescriptorDataInfoEXT where
withCStruct :: forall b.
BufferCaptureDescriptorDataInfoEXT
-> (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT) -> IO b)
-> IO b
withCStruct BufferCaptureDescriptorDataInfoEXT
x ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p BufferCaptureDescriptorDataInfoEXT
x (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT) -> IO b
f "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> BufferCaptureDescriptorDataInfoEXT -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p BufferCaptureDescriptorDataInfoEXT{Buffer
buffer :: Buffer
$sel:buffer:BufferCaptureDescriptorDataInfoEXT :: BufferCaptureDescriptorDataInfoEXT -> Buffer
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (Buffer
buffer)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct BufferCaptureDescriptorDataInfoEXT where
peekCStruct :: ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> IO BufferCaptureDescriptorDataInfoEXT
peekCStruct "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p = do
Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer (("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Buffer -> BufferCaptureDescriptorDataInfoEXT
BufferCaptureDescriptorDataInfoEXT
Buffer
buffer
instance Storable BufferCaptureDescriptorDataInfoEXT where
sizeOf :: BufferCaptureDescriptorDataInfoEXT -> Int
sizeOf ~BufferCaptureDescriptorDataInfoEXT
_ = Int
24
alignment :: BufferCaptureDescriptorDataInfoEXT -> Int
alignment ~BufferCaptureDescriptorDataInfoEXT
_ = Int
8
peek :: ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> IO BufferCaptureDescriptorDataInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT)
-> BufferCaptureDescriptorDataInfoEXT -> IO ()
poke "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
ptr BufferCaptureDescriptorDataInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr BufferCaptureDescriptorDataInfoEXT
ptr BufferCaptureDescriptorDataInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero BufferCaptureDescriptorDataInfoEXT where
zero :: BufferCaptureDescriptorDataInfoEXT
zero = Buffer -> BufferCaptureDescriptorDataInfoEXT
BufferCaptureDescriptorDataInfoEXT
forall a. Zero a => a
zero
data ImageCaptureDescriptorDataInfoEXT = ImageCaptureDescriptorDataInfoEXT
{
ImageCaptureDescriptorDataInfoEXT -> Image
image :: Image }
deriving (Typeable, ImageCaptureDescriptorDataInfoEXT
-> ImageCaptureDescriptorDataInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageCaptureDescriptorDataInfoEXT
-> ImageCaptureDescriptorDataInfoEXT -> Bool
$c/= :: ImageCaptureDescriptorDataInfoEXT
-> ImageCaptureDescriptorDataInfoEXT -> Bool
== :: ImageCaptureDescriptorDataInfoEXT
-> ImageCaptureDescriptorDataInfoEXT -> Bool
$c== :: ImageCaptureDescriptorDataInfoEXT
-> ImageCaptureDescriptorDataInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageCaptureDescriptorDataInfoEXT)
#endif
deriving instance Show ImageCaptureDescriptorDataInfoEXT
instance ToCStruct ImageCaptureDescriptorDataInfoEXT where
withCStruct :: forall b.
ImageCaptureDescriptorDataInfoEXT
-> (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT) -> IO b)
-> IO b
withCStruct ImageCaptureDescriptorDataInfoEXT
x ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p ImageCaptureDescriptorDataInfoEXT
x (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT) -> IO b
f "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ImageCaptureDescriptorDataInfoEXT -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p ImageCaptureDescriptorDataInfoEXT{Image
image :: Image
$sel:image:ImageCaptureDescriptorDataInfoEXT :: ImageCaptureDescriptorDataInfoEXT -> Image
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Image)) (Image
image)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Image)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageCaptureDescriptorDataInfoEXT where
peekCStruct :: ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> IO ImageCaptureDescriptorDataInfoEXT
peekCStruct "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p = do
Image
image <- forall a. Storable a => Ptr a -> IO a
peek @Image (("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Image))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Image -> ImageCaptureDescriptorDataInfoEXT
ImageCaptureDescriptorDataInfoEXT
Image
image
instance Storable ImageCaptureDescriptorDataInfoEXT where
sizeOf :: ImageCaptureDescriptorDataInfoEXT -> Int
sizeOf ~ImageCaptureDescriptorDataInfoEXT
_ = Int
24
alignment :: ImageCaptureDescriptorDataInfoEXT -> Int
alignment ~ImageCaptureDescriptorDataInfoEXT
_ = Int
8
peek :: ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> IO ImageCaptureDescriptorDataInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT)
-> ImageCaptureDescriptorDataInfoEXT -> IO ()
poke "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
ptr ImageCaptureDescriptorDataInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageCaptureDescriptorDataInfoEXT
ptr ImageCaptureDescriptorDataInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageCaptureDescriptorDataInfoEXT where
zero :: ImageCaptureDescriptorDataInfoEXT
zero = Image -> ImageCaptureDescriptorDataInfoEXT
ImageCaptureDescriptorDataInfoEXT
forall a. Zero a => a
zero
data ImageViewCaptureDescriptorDataInfoEXT = ImageViewCaptureDescriptorDataInfoEXT
{
ImageViewCaptureDescriptorDataInfoEXT -> ImageView
imageView :: ImageView }
deriving (Typeable, ImageViewCaptureDescriptorDataInfoEXT
-> ImageViewCaptureDescriptorDataInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewCaptureDescriptorDataInfoEXT
-> ImageViewCaptureDescriptorDataInfoEXT -> Bool
$c/= :: ImageViewCaptureDescriptorDataInfoEXT
-> ImageViewCaptureDescriptorDataInfoEXT -> Bool
== :: ImageViewCaptureDescriptorDataInfoEXT
-> ImageViewCaptureDescriptorDataInfoEXT -> Bool
$c== :: ImageViewCaptureDescriptorDataInfoEXT
-> ImageViewCaptureDescriptorDataInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewCaptureDescriptorDataInfoEXT)
#endif
deriving instance Show ImageViewCaptureDescriptorDataInfoEXT
instance ToCStruct ImageViewCaptureDescriptorDataInfoEXT where
withCStruct :: forall b.
ImageViewCaptureDescriptorDataInfoEXT
-> (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> IO b)
-> IO b
withCStruct ImageViewCaptureDescriptorDataInfoEXT
x ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p ImageViewCaptureDescriptorDataInfoEXT
x (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT) -> IO b
f "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ImageViewCaptureDescriptorDataInfoEXT -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p ImageViewCaptureDescriptorDataInfoEXT{ImageView
imageView :: ImageView
$sel:imageView:ImageViewCaptureDescriptorDataInfoEXT :: ImageViewCaptureDescriptorDataInfoEXT -> ImageView
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageView)) (ImageView
imageView)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageView)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageViewCaptureDescriptorDataInfoEXT where
peekCStruct :: ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> IO ImageViewCaptureDescriptorDataInfoEXT
peekCStruct "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p = do
ImageView
imageView <- forall a. Storable a => Ptr a -> IO a
peek @ImageView (("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageView))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ImageView -> ImageViewCaptureDescriptorDataInfoEXT
ImageViewCaptureDescriptorDataInfoEXT
ImageView
imageView
instance Storable ImageViewCaptureDescriptorDataInfoEXT where
sizeOf :: ImageViewCaptureDescriptorDataInfoEXT -> Int
sizeOf ~ImageViewCaptureDescriptorDataInfoEXT
_ = Int
24
alignment :: ImageViewCaptureDescriptorDataInfoEXT -> Int
alignment ~ImageViewCaptureDescriptorDataInfoEXT
_ = Int
8
peek :: ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> IO ImageViewCaptureDescriptorDataInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT)
-> ImageViewCaptureDescriptorDataInfoEXT -> IO ()
poke "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
ptr ImageViewCaptureDescriptorDataInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageViewCaptureDescriptorDataInfoEXT
ptr ImageViewCaptureDescriptorDataInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewCaptureDescriptorDataInfoEXT where
zero :: ImageViewCaptureDescriptorDataInfoEXT
zero = ImageView -> ImageViewCaptureDescriptorDataInfoEXT
ImageViewCaptureDescriptorDataInfoEXT
forall a. Zero a => a
zero
data SamplerCaptureDescriptorDataInfoEXT = SamplerCaptureDescriptorDataInfoEXT
{
SamplerCaptureDescriptorDataInfoEXT -> Sampler
sampler :: Sampler }
deriving (Typeable, SamplerCaptureDescriptorDataInfoEXT
-> SamplerCaptureDescriptorDataInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SamplerCaptureDescriptorDataInfoEXT
-> SamplerCaptureDescriptorDataInfoEXT -> Bool
$c/= :: SamplerCaptureDescriptorDataInfoEXT
-> SamplerCaptureDescriptorDataInfoEXT -> Bool
== :: SamplerCaptureDescriptorDataInfoEXT
-> SamplerCaptureDescriptorDataInfoEXT -> Bool
$c== :: SamplerCaptureDescriptorDataInfoEXT
-> SamplerCaptureDescriptorDataInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SamplerCaptureDescriptorDataInfoEXT)
#endif
deriving instance Show SamplerCaptureDescriptorDataInfoEXT
instance ToCStruct SamplerCaptureDescriptorDataInfoEXT where
withCStruct :: forall b.
SamplerCaptureDescriptorDataInfoEXT
-> (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT) -> IO b)
-> IO b
withCStruct SamplerCaptureDescriptorDataInfoEXT
x ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p SamplerCaptureDescriptorDataInfoEXT
x (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT) -> IO b
f "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> SamplerCaptureDescriptorDataInfoEXT -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p SamplerCaptureDescriptorDataInfoEXT{Sampler
sampler :: Sampler
$sel:sampler:SamplerCaptureDescriptorDataInfoEXT :: SamplerCaptureDescriptorDataInfoEXT -> Sampler
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Sampler)) (Sampler
sampler)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Sampler)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SamplerCaptureDescriptorDataInfoEXT where
peekCStruct :: ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> IO SamplerCaptureDescriptorDataInfoEXT
peekCStruct "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p = do
Sampler
sampler <- forall a. Storable a => Ptr a -> IO a
peek @Sampler (("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Sampler))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Sampler -> SamplerCaptureDescriptorDataInfoEXT
SamplerCaptureDescriptorDataInfoEXT
Sampler
sampler
instance Storable SamplerCaptureDescriptorDataInfoEXT where
sizeOf :: SamplerCaptureDescriptorDataInfoEXT -> Int
sizeOf ~SamplerCaptureDescriptorDataInfoEXT
_ = Int
24
alignment :: SamplerCaptureDescriptorDataInfoEXT -> Int
alignment ~SamplerCaptureDescriptorDataInfoEXT
_ = Int
8
peek :: ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> IO SamplerCaptureDescriptorDataInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT)
-> SamplerCaptureDescriptorDataInfoEXT -> IO ()
poke "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
ptr SamplerCaptureDescriptorDataInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr SamplerCaptureDescriptorDataInfoEXT
ptr SamplerCaptureDescriptorDataInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SamplerCaptureDescriptorDataInfoEXT where
zero :: SamplerCaptureDescriptorDataInfoEXT
zero = Sampler -> SamplerCaptureDescriptorDataInfoEXT
SamplerCaptureDescriptorDataInfoEXT
forall a. Zero a => a
zero
data AccelerationStructureCaptureDescriptorDataInfoEXT = AccelerationStructureCaptureDescriptorDataInfoEXT
{
AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureKHR
accelerationStructure :: AccelerationStructureKHR
,
AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureNV
accelerationStructureNV :: AccelerationStructureNV
}
deriving (Typeable, AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureCaptureDescriptorDataInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureCaptureDescriptorDataInfoEXT -> Bool
$c/= :: AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureCaptureDescriptorDataInfoEXT -> Bool
== :: AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureCaptureDescriptorDataInfoEXT -> Bool
$c== :: AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureCaptureDescriptorDataInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureCaptureDescriptorDataInfoEXT)
#endif
deriving instance Show AccelerationStructureCaptureDescriptorDataInfoEXT
instance ToCStruct AccelerationStructureCaptureDescriptorDataInfoEXT where
withCStruct :: forall b.
AccelerationStructureCaptureDescriptorDataInfoEXT
-> (("pInfo"
::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> IO b)
-> IO b
withCStruct AccelerationStructureCaptureDescriptorDataInfoEXT
x ("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p AccelerationStructureCaptureDescriptorDataInfoEXT
x (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> IO b
f "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> AccelerationStructureCaptureDescriptorDataInfoEXT
-> IO b
-> IO b
pokeCStruct "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p AccelerationStructureCaptureDescriptorDataInfoEXT{AccelerationStructureNV
AccelerationStructureKHR
accelerationStructureNV :: AccelerationStructureNV
accelerationStructure :: AccelerationStructureKHR
$sel:accelerationStructureNV:AccelerationStructureCaptureDescriptorDataInfoEXT :: AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureNV
$sel:accelerationStructure:AccelerationStructureCaptureDescriptorDataInfoEXT :: AccelerationStructureCaptureDescriptorDataInfoEXT
-> AccelerationStructureKHR
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
accelerationStructure)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr AccelerationStructureNV)) (AccelerationStructureNV
accelerationStructureNV)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CAPTURE_DESCRIPTOR_DATA_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct AccelerationStructureCaptureDescriptorDataInfoEXT where
peekCStruct :: ("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> IO AccelerationStructureCaptureDescriptorDataInfoEXT
peekCStruct "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p = do
AccelerationStructureKHR
accelerationStructure <- forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccelerationStructureKHR))
AccelerationStructureNV
accelerationStructureNV <- forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureNV (("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr AccelerationStructureNV))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ AccelerationStructureKHR
-> AccelerationStructureNV
-> AccelerationStructureCaptureDescriptorDataInfoEXT
AccelerationStructureCaptureDescriptorDataInfoEXT
AccelerationStructureKHR
accelerationStructure AccelerationStructureNV
accelerationStructureNV
instance Storable AccelerationStructureCaptureDescriptorDataInfoEXT where
sizeOf :: AccelerationStructureCaptureDescriptorDataInfoEXT -> Int
sizeOf ~AccelerationStructureCaptureDescriptorDataInfoEXT
_ = Int
32
alignment :: AccelerationStructureCaptureDescriptorDataInfoEXT -> Int
alignment ~AccelerationStructureCaptureDescriptorDataInfoEXT
_ = Int
8
peek :: ("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> IO AccelerationStructureCaptureDescriptorDataInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT)
-> AccelerationStructureCaptureDescriptorDataInfoEXT -> IO ()
poke "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
ptr AccelerationStructureCaptureDescriptorDataInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr AccelerationStructureCaptureDescriptorDataInfoEXT
ptr AccelerationStructureCaptureDescriptorDataInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AccelerationStructureCaptureDescriptorDataInfoEXT where
zero :: AccelerationStructureCaptureDescriptorDataInfoEXT
zero = AccelerationStructureKHR
-> AccelerationStructureNV
-> AccelerationStructureCaptureDescriptorDataInfoEXT
AccelerationStructureCaptureDescriptorDataInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data OpaqueCaptureDescriptorDataCreateInfoEXT = OpaqueCaptureDescriptorDataCreateInfoEXT
{
OpaqueCaptureDescriptorDataCreateInfoEXT -> "descriptor" ::: Ptr ()
opaqueCaptureDescriptorData :: Ptr () }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (OpaqueCaptureDescriptorDataCreateInfoEXT)
#endif
deriving instance Show OpaqueCaptureDescriptorDataCreateInfoEXT
instance ToCStruct OpaqueCaptureDescriptorDataCreateInfoEXT where
withCStruct :: forall b.
OpaqueCaptureDescriptorDataCreateInfoEXT
-> (Ptr OpaqueCaptureDescriptorDataCreateInfoEXT -> IO b) -> IO b
withCStruct OpaqueCaptureDescriptorDataCreateInfoEXT
x Ptr OpaqueCaptureDescriptorDataCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p OpaqueCaptureDescriptorDataCreateInfoEXT
x (Ptr OpaqueCaptureDescriptorDataCreateInfoEXT -> IO b
f Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
-> OpaqueCaptureDescriptorDataCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p OpaqueCaptureDescriptorDataCreateInfoEXT{"descriptor" ::: Ptr ()
opaqueCaptureDescriptorData :: "descriptor" ::: Ptr ()
$sel:opaqueCaptureDescriptorData:OpaqueCaptureDescriptorDataCreateInfoEXT :: OpaqueCaptureDescriptorDataCreateInfoEXT -> "descriptor" ::: Ptr ()
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_OPAQUE_CAPTURE_DESCRIPTOR_DATA_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ()))) ("descriptor" ::: Ptr ()
opaqueCaptureDescriptorData)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr OpaqueCaptureDescriptorDataCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_OPAQUE_CAPTURE_DESCRIPTOR_DATA_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ()))) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct OpaqueCaptureDescriptorDataCreateInfoEXT where
peekCStruct :: Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
-> IO OpaqueCaptureDescriptorDataCreateInfoEXT
peekCStruct Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p = do
"descriptor" ::: Ptr ()
opaqueCaptureDescriptorData <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ())))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("descriptor" ::: Ptr ())
-> OpaqueCaptureDescriptorDataCreateInfoEXT
OpaqueCaptureDescriptorDataCreateInfoEXT
"descriptor" ::: Ptr ()
opaqueCaptureDescriptorData
instance Storable OpaqueCaptureDescriptorDataCreateInfoEXT where
sizeOf :: OpaqueCaptureDescriptorDataCreateInfoEXT -> Int
sizeOf ~OpaqueCaptureDescriptorDataCreateInfoEXT
_ = Int
24
alignment :: OpaqueCaptureDescriptorDataCreateInfoEXT -> Int
alignment ~OpaqueCaptureDescriptorDataCreateInfoEXT
_ = Int
8
peek :: Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
-> IO OpaqueCaptureDescriptorDataCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
-> OpaqueCaptureDescriptorDataCreateInfoEXT -> IO ()
poke Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
ptr OpaqueCaptureDescriptorDataCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr OpaqueCaptureDescriptorDataCreateInfoEXT
ptr OpaqueCaptureDescriptorDataCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero OpaqueCaptureDescriptorDataCreateInfoEXT where
zero :: OpaqueCaptureDescriptorDataCreateInfoEXT
zero = ("descriptor" ::: Ptr ())
-> OpaqueCaptureDescriptorDataCreateInfoEXT
OpaqueCaptureDescriptorDataCreateInfoEXT
forall a. Zero a => a
zero
data DescriptorDataEXT
= ASampler Sampler
| ACombinedImageSampler DescriptorImageInfo
| AnInputAttachmentImage DescriptorImageInfo
| ASampledImage (Maybe DescriptorImageInfo)
| AStorageImage (Maybe DescriptorImageInfo)
| AnUniformTexelBuffer (Maybe DescriptorAddressInfoEXT)
| AStorageTexelBuffer (Maybe DescriptorAddressInfoEXT)
| AnUniformBuffer (Maybe DescriptorAddressInfoEXT)
| AStorageBuffer (Maybe DescriptorAddressInfoEXT)
| AnAccelerationStructure DeviceAddress
deriving (Int -> DescriptorDataEXT -> ShowS
[DescriptorDataEXT] -> ShowS
DescriptorDataEXT -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescriptorDataEXT] -> ShowS
$cshowList :: [DescriptorDataEXT] -> ShowS
show :: DescriptorDataEXT -> String
$cshow :: DescriptorDataEXT -> String
showsPrec :: Int -> DescriptorDataEXT -> ShowS
$cshowsPrec :: Int -> DescriptorDataEXT -> ShowS
Show)
instance ToCStruct DescriptorDataEXT where
withCStruct :: forall b.
DescriptorDataEXT -> (Ptr DescriptorDataEXT -> IO b) -> IO b
withCStruct DescriptorDataEXT
x Ptr DescriptorDataEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 forall a b. (a -> b) -> a -> b
$ \Ptr DescriptorDataEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorDataEXT
p DescriptorDataEXT
x (Ptr DescriptorDataEXT -> IO b
f Ptr DescriptorDataEXT
p)
pokeCStruct :: Ptr DescriptorDataEXT -> DescriptorDataEXT -> IO a -> IO a
pokeCStruct :: forall b.
Ptr DescriptorDataEXT -> DescriptorDataEXT -> IO b -> IO b
pokeCStruct Ptr DescriptorDataEXT
p = (forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
ContT r m a -> (a -> m r) -> m r
runContT forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
ASampler Sampler
v -> do
Ptr Sampler
pSampler <- 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. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Sampler
v)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr Sampler) Ptr DescriptorDataEXT
p) Ptr Sampler
pSampler
ACombinedImageSampler DescriptorImageInfo
v -> do
Ptr DescriptorImageInfo
pCombinedImageSampler <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorImageInfo
v)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p) Ptr DescriptorImageInfo
pCombinedImageSampler
AnInputAttachmentImage DescriptorImageInfo
v -> do
Ptr DescriptorImageInfo
pInputAttachmentImage <- 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorImageInfo
v)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p) Ptr DescriptorImageInfo
pInputAttachmentImage
ASampledImage Maybe DescriptorImageInfo
v -> do
Ptr DescriptorImageInfo
pSampledImage <- case (Maybe DescriptorImageInfo
v) of
Maybe DescriptorImageInfo
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just DescriptorImageInfo
j -> 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorImageInfo
j)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p) Ptr DescriptorImageInfo
pSampledImage
AStorageImage Maybe DescriptorImageInfo
v -> do
Ptr DescriptorImageInfo
pStorageImage <- case (Maybe DescriptorImageInfo
v) of
Maybe DescriptorImageInfo
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just DescriptorImageInfo
j -> 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorImageInfo
j)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p) Ptr DescriptorImageInfo
pStorageImage
AnUniformTexelBuffer Maybe DescriptorAddressInfoEXT
v -> do
Ptr DescriptorAddressInfoEXT
pUniformTexelBuffer <- case (Maybe DescriptorAddressInfoEXT
v) of
Maybe DescriptorAddressInfoEXT
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just DescriptorAddressInfoEXT
j -> 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorAddressInfoEXT
j)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p) Ptr DescriptorAddressInfoEXT
pUniformTexelBuffer
AStorageTexelBuffer Maybe DescriptorAddressInfoEXT
v -> do
Ptr DescriptorAddressInfoEXT
pStorageTexelBuffer <- case (Maybe DescriptorAddressInfoEXT
v) of
Maybe DescriptorAddressInfoEXT
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just DescriptorAddressInfoEXT
j -> 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorAddressInfoEXT
j)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p) Ptr DescriptorAddressInfoEXT
pStorageTexelBuffer
AnUniformBuffer Maybe DescriptorAddressInfoEXT
v -> do
Ptr DescriptorAddressInfoEXT
pUniformBuffer <- case (Maybe DescriptorAddressInfoEXT
v) of
Maybe DescriptorAddressInfoEXT
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just DescriptorAddressInfoEXT
j -> 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorAddressInfoEXT
j)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p) Ptr DescriptorAddressInfoEXT
pUniformBuffer
AStorageBuffer Maybe DescriptorAddressInfoEXT
v -> do
Ptr DescriptorAddressInfoEXT
pStorageBuffer <- case (Maybe DescriptorAddressInfoEXT
v) of
Maybe DescriptorAddressInfoEXT
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just DescriptorAddressInfoEXT
j -> 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 => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorAddressInfoEXT
j)
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 (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p) Ptr DescriptorAddressInfoEXT
pStorageBuffer
AnAccelerationStructure DeviceAddress
v -> 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 (forall a b. Ptr a -> Ptr b
castPtr @_ @DeviceAddress Ptr DescriptorDataEXT
p) (DeviceAddress
v)
pokeZeroCStruct :: Ptr DescriptorDataEXT -> IO b -> IO b
pokeZeroCStruct :: forall b. Ptr DescriptorDataEXT -> IO b -> IO b
pokeZeroCStruct Ptr DescriptorDataEXT
_ IO b
f = IO b
f
cStructSize :: Int
cStructSize = Int
8
cStructAlignment :: Int
cStructAlignment = Int
8
instance Zero DescriptorDataEXT where
zero :: DescriptorDataEXT
zero = Sampler -> DescriptorDataEXT
ASampler forall a. Zero a => a
zero
peekDescriptorDataEXT :: DescriptorType -> Ptr DescriptorDataEXT -> IO DescriptorDataEXT
peekDescriptorDataEXT :: DescriptorType -> Ptr DescriptorDataEXT -> IO DescriptorDataEXT
peekDescriptorDataEXT DescriptorType
tag Ptr DescriptorDataEXT
p = case DescriptorType
tag of
DescriptorType
DESCRIPTOR_TYPE_SAMPLER -> Sampler -> DescriptorDataEXT
ASampler forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Storable a => Ptr a -> IO a
peek @Sampler forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr Sampler) Ptr DescriptorDataEXT
p))
DescriptorType
DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER -> DescriptorImageInfo -> DescriptorDataEXT
ACombinedImageSampler forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorImageInfo forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p))
DescriptorType
DESCRIPTOR_TYPE_INPUT_ATTACHMENT -> DescriptorImageInfo -> DescriptorDataEXT
AnInputAttachmentImage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorImageInfo forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p))
DescriptorType
DESCRIPTOR_TYPE_SAMPLED_IMAGE -> Maybe DescriptorImageInfo -> DescriptorDataEXT
ASampledImage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Ptr DescriptorImageInfo
pSampledImage <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorImageInfo) (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr DescriptorImageInfo
j -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorImageInfo (Ptr DescriptorImageInfo
j)) Ptr DescriptorImageInfo
pSampledImage)
DescriptorType
DESCRIPTOR_TYPE_STORAGE_IMAGE -> Maybe DescriptorImageInfo -> DescriptorDataEXT
AStorageImage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Ptr DescriptorImageInfo
pStorageImage <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorImageInfo) (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorImageInfo) Ptr DescriptorDataEXT
p)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr DescriptorImageInfo
j -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorImageInfo (Ptr DescriptorImageInfo
j)) Ptr DescriptorImageInfo
pStorageImage)
DescriptorType
DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER -> Maybe DescriptorAddressInfoEXT -> DescriptorDataEXT
AnUniformTexelBuffer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Ptr DescriptorAddressInfoEXT
pUniformTexelBuffer <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorAddressInfoEXT) (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr DescriptorAddressInfoEXT
j -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorAddressInfoEXT (Ptr DescriptorAddressInfoEXT
j)) Ptr DescriptorAddressInfoEXT
pUniformTexelBuffer)
DescriptorType
DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER -> Maybe DescriptorAddressInfoEXT -> DescriptorDataEXT
AStorageTexelBuffer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Ptr DescriptorAddressInfoEXT
pStorageTexelBuffer <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorAddressInfoEXT) (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr DescriptorAddressInfoEXT
j -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorAddressInfoEXT (Ptr DescriptorAddressInfoEXT
j)) Ptr DescriptorAddressInfoEXT
pStorageTexelBuffer)
DescriptorType
DESCRIPTOR_TYPE_UNIFORM_BUFFER -> Maybe DescriptorAddressInfoEXT -> DescriptorDataEXT
AnUniformBuffer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Ptr DescriptorAddressInfoEXT
pUniformBuffer <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorAddressInfoEXT) (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr DescriptorAddressInfoEXT
j -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorAddressInfoEXT (Ptr DescriptorAddressInfoEXT
j)) Ptr DescriptorAddressInfoEXT
pUniformBuffer)
DescriptorType
DESCRIPTOR_TYPE_STORAGE_BUFFER -> Maybe DescriptorAddressInfoEXT -> DescriptorDataEXT
AStorageBuffer forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Ptr DescriptorAddressInfoEXT
pStorageBuffer <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorAddressInfoEXT) (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr DescriptorAddressInfoEXT) Ptr DescriptorDataEXT
p)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr DescriptorAddressInfoEXT
j -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DescriptorAddressInfoEXT (Ptr DescriptorAddressInfoEXT
j)) Ptr DescriptorAddressInfoEXT
pStorageBuffer)
DescriptorType
DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR -> DeviceAddress -> DescriptorDataEXT
AnAccelerationStructure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress (forall a b. Ptr a -> Ptr b
castPtr @_ @DeviceAddress Ptr DescriptorDataEXT
p))
type EXT_DESCRIPTOR_BUFFER_SPEC_VERSION = 1
pattern EXT_DESCRIPTOR_BUFFER_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DESCRIPTOR_BUFFER_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DESCRIPTOR_BUFFER_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DESCRIPTOR_BUFFER_SPEC_VERSION = 1
type EXT_DESCRIPTOR_BUFFER_EXTENSION_NAME = "VK_EXT_descriptor_buffer"
pattern EXT_DESCRIPTOR_BUFFER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DESCRIPTOR_BUFFER_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DESCRIPTOR_BUFFER_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DESCRIPTOR_BUFFER_EXTENSION_NAME = "VK_EXT_descriptor_buffer"