{-# language CPP #-}
-- No documentation found for Chapter "Promoted_From_VK_EXT_descriptor_indexing"
module Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing  ( PhysicalDeviceDescriptorIndexingFeatures(..)
                                                               , PhysicalDeviceDescriptorIndexingProperties(..)
                                                               , DescriptorSetLayoutBindingFlagsCreateInfo(..)
                                                               , DescriptorSetVariableDescriptorCountAllocateInfo(..)
                                                               , DescriptorSetVariableDescriptorCountLayoutSupport(..)
                                                               , StructureType(..)
                                                               , Result(..)
                                                               , DescriptorPoolCreateFlagBits(..)
                                                               , DescriptorPoolCreateFlags
                                                               , DescriptorSetLayoutCreateFlagBits(..)
                                                               , DescriptorSetLayoutCreateFlags
                                                               , DescriptorBindingFlagBits(..)
                                                               , DescriptorBindingFlags
                                                               ) where

import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core12.Enums.DescriptorBindingFlagBits (DescriptorBindingFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES))
import Vulkan.Core12.Enums.DescriptorBindingFlagBits (DescriptorBindingFlagBits(..))
import Vulkan.Core12.Enums.DescriptorBindingFlagBits (DescriptorBindingFlags)
import Vulkan.Core10.Enums.DescriptorPoolCreateFlagBits (DescriptorPoolCreateFlagBits(..))
import Vulkan.Core10.Enums.DescriptorPoolCreateFlagBits (DescriptorPoolCreateFlags)
import Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits (DescriptorSetLayoutCreateFlagBits(..))
import Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits (DescriptorSetLayoutCreateFlags)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
-- | VkPhysicalDeviceDescriptorIndexingFeatures - Structure describing
-- descriptor indexing features that can be supported by an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceDescriptorIndexingFeatures' structure is included
-- in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceDescriptorIndexingFeatures' /can/ also be used
-- in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_descriptor_indexing VK_EXT_descriptor_indexing>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDescriptorIndexingFeatures = PhysicalDeviceDescriptorIndexingFeatures
  { -- | #extension-features-shaderInputAttachmentArrayDynamicIndexing#
    -- @shaderInputAttachmentArrayDynamicIndexing@ indicates whether arrays of
    -- input attachments /can/ be indexed by dynamically uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @InputAttachmentArrayDynamicIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderInputAttachmentArrayDynamicIndexing :: Bool
  , -- | #extension-features-shaderUniformTexelBufferArrayDynamicIndexing#
    -- @shaderUniformTexelBufferArrayDynamicIndexing@ indicates whether arrays
    -- of uniform texel buffers /can/ be indexed by dynamically uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @UniformTexelBufferArrayDynamicIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderUniformTexelBufferArrayDynamicIndexing :: Bool
  , -- | #extension-features-shaderStorageTexelBufferArrayDynamicIndexing#
    -- @shaderStorageTexelBufferArrayDynamicIndexing@ indicates whether arrays
    -- of storage texel buffers /can/ be indexed by dynamically uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @StorageTexelBufferArrayDynamicIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderStorageTexelBufferArrayDynamicIndexing :: Bool
  , -- | #extension-features-shaderUniformBufferArrayNonUniformIndexing#
    -- @shaderUniformBufferArrayNonUniformIndexing@ indicates whether arrays of
    -- uniform buffers /can/ be indexed by non-uniform integer expressions in
    -- shader code. If this feature is not enabled, resources with a descriptor
    -- type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @UniformBufferArrayNonUniformIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderUniformBufferArrayNonUniformIndexing :: Bool
  , -- | #extension-features-shaderSampledImageArrayNonUniformIndexing#
    -- @shaderSampledImageArrayNonUniformIndexing@ indicates whether arrays of
    -- samplers or sampled images /can/ be indexed by non-uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
    -- or 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @SampledImageArrayNonUniformIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderSampledImageArrayNonUniformIndexing :: Bool
  , -- | #extension-features-shaderStorageBufferArrayNonUniformIndexing#
    -- @shaderStorageBufferArrayNonUniformIndexing@ indicates whether arrays of
    -- storage buffers /can/ be indexed by non-uniform integer expressions in
    -- shader code. If this feature is not enabled, resources with a descriptor
    -- type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @StorageBufferArrayNonUniformIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderStorageBufferArrayNonUniformIndexing :: Bool
  , -- | #extension-features-shaderStorageImageArrayNonUniformIndexing#
    -- @shaderStorageImageArrayNonUniformIndexing@ indicates whether arrays of
    -- storage images /can/ be indexed by non-uniform integer expressions in
    -- shader code. If this feature is not enabled, resources with a descriptor
    -- type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @StorageImageArrayNonUniformIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderStorageImageArrayNonUniformIndexing :: Bool
  , -- | #extension-features-shaderInputAttachmentArrayNonUniformIndexing#
    -- @shaderInputAttachmentArrayNonUniformIndexing@ indicates whether arrays
    -- of input attachments /can/ be indexed by non-uniform integer expressions
    -- in shader code. If this feature is not enabled, resources with a
    -- descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @InputAttachmentArrayNonUniformIndexing@ capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderInputAttachmentArrayNonUniformIndexing :: Bool
  , -- | #extension-features-shaderUniformTexelBufferArrayNonUniformIndexing#
    -- @shaderUniformTexelBufferArrayNonUniformIndexing@ indicates whether
    -- arrays of uniform texel buffers /can/ be indexed by non-uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @UniformTexelBufferArrayNonUniformIndexing@
    -- capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderUniformTexelBufferArrayNonUniformIndexing :: Bool
  , -- | #extension-features-shaderStorageTexelBufferArrayNonUniformIndexing#
    -- @shaderStorageTexelBufferArrayNonUniformIndexing@ indicates whether
    -- arrays of storage texel buffers /can/ be indexed by non-uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
    -- /must/ not be indexed by non-uniform integer expressions when aggregated
    -- into arrays in shader code. This also indicates whether shader modules
    -- /can/ declare the @StorageTexelBufferArrayNonUniformIndexing@
    -- capability.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
shaderStorageTexelBufferArrayNonUniformIndexing :: Bool
  , -- | #extension-features-descriptorBindingUniformBufferUpdateAfterBind#
    -- @descriptorBindingUniformBufferUpdateAfterBind@ indicates whether the
    -- implementation supports updating uniform buffer descriptors after a set
    -- is bound. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
    -- /must/ not be used with
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER'.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingUniformBufferUpdateAfterBind :: Bool
  , -- | #extension-features-descriptorBindingSampledImageUpdateAfterBind#
    -- @descriptorBindingSampledImageUpdateAfterBind@ indicates whether the
    -- implementation supports updating sampled image descriptors after a set
    -- is bound. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
    -- /must/ not be used with
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
    -- or 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingSampledImageUpdateAfterBind :: Bool
  , -- | #extension-features-descriptorBindingStorageImageUpdateAfterBind#
    -- @descriptorBindingStorageImageUpdateAfterBind@ indicates whether the
    -- implementation supports updating storage image descriptors after a set
    -- is bound. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
    -- /must/ not be used with
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE'.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingStorageImageUpdateAfterBind :: Bool
  , -- | #extension-features-descriptorBindingStorageBufferUpdateAfterBind#
    -- @descriptorBindingStorageBufferUpdateAfterBind@ indicates whether the
    -- implementation supports updating storage buffer descriptors after a set
    -- is bound. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
    -- /must/ not be used with
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER'.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingStorageBufferUpdateAfterBind :: Bool
  , -- | #extension-features-descriptorBindingUniformTexelBufferUpdateAfterBind#
    -- @descriptorBindingUniformTexelBufferUpdateAfterBind@ indicates whether
    -- the implementation supports updating uniform texel buffer descriptors
    -- after a set is bound. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
    -- /must/ not be used with
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
  , -- | #extension-features-descriptorBindingStorageTexelBufferUpdateAfterBind#
    -- @descriptorBindingStorageTexelBufferUpdateAfterBind@ indicates whether
    -- the implementation supports updating storage texel buffer descriptors
    -- after a set is bound. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
    -- /must/ not be used with
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
  , -- | #extension-features-descriptorBindingUpdateUnusedWhilePending#
    -- @descriptorBindingUpdateUnusedWhilePending@ indicates whether the
    -- implementation supports updating descriptors while the set is in use. If
    -- this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT'
    -- /must/ not be used.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingUpdateUnusedWhilePending :: Bool
  , -- | #extension-features-descriptorBindingPartiallyBound#
    -- @descriptorBindingPartiallyBound@ indicates whether the implementation
    -- supports statically using a descriptor set binding in which some
    -- descriptors are not valid. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_PARTIALLY_BOUND_BIT'
    -- /must/ not be used.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingPartiallyBound :: Bool
  , -- | #extension-features-descriptorBindingVariableDescriptorCount#
    -- @descriptorBindingVariableDescriptorCount@ indicates whether the
    -- implementation supports descriptor sets with a variable-sized last
    -- binding. If this feature is not enabled,
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT'
    -- /must/ not be used.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
descriptorBindingVariableDescriptorCount :: Bool
  , -- | #extension-features-runtimeDescriptorArray# @runtimeDescriptorArray@
    -- indicates whether the implementation supports the SPIR-V
    -- @RuntimeDescriptorArray@ capability. If this feature is not enabled,
    -- descriptors /must/ not be declared in runtime arrays.
    PhysicalDeviceDescriptorIndexingFeatures -> Bool
runtimeDescriptorArray :: Bool
  }
  deriving (Typeable, PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> Bool
$c/= :: PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> Bool
== :: PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> Bool
$c== :: PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDescriptorIndexingFeatures)
#endif
deriving instance Show PhysicalDeviceDescriptorIndexingFeatures

instance ToCStruct PhysicalDeviceDescriptorIndexingFeatures where
  withCStruct :: forall b.
PhysicalDeviceDescriptorIndexingFeatures
-> (Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceDescriptorIndexingFeatures
x Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
96 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDescriptorIndexingFeatures
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingFeatures
p PhysicalDeviceDescriptorIndexingFeatures
x (Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b
f Ptr PhysicalDeviceDescriptorIndexingFeatures
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingFeatures
p PhysicalDeviceDescriptorIndexingFeatures{Bool
runtimeDescriptorArray :: Bool
descriptorBindingVariableDescriptorCount :: Bool
descriptorBindingPartiallyBound :: Bool
descriptorBindingUpdateUnusedWhilePending :: Bool
descriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
descriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
descriptorBindingStorageBufferUpdateAfterBind :: Bool
descriptorBindingStorageImageUpdateAfterBind :: Bool
descriptorBindingSampledImageUpdateAfterBind :: Bool
descriptorBindingUniformBufferUpdateAfterBind :: Bool
shaderStorageTexelBufferArrayNonUniformIndexing :: Bool
shaderUniformTexelBufferArrayNonUniformIndexing :: Bool
shaderInputAttachmentArrayNonUniformIndexing :: Bool
shaderStorageImageArrayNonUniformIndexing :: Bool
shaderStorageBufferArrayNonUniformIndexing :: Bool
shaderSampledImageArrayNonUniformIndexing :: Bool
shaderUniformBufferArrayNonUniformIndexing :: Bool
shaderStorageTexelBufferArrayDynamicIndexing :: Bool
shaderUniformTexelBufferArrayDynamicIndexing :: Bool
shaderInputAttachmentArrayDynamicIndexing :: Bool
$sel:runtimeDescriptorArray:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingVariableDescriptorCount:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingPartiallyBound:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingUpdateUnusedWhilePending:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingStorageTexelBufferUpdateAfterBind:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingUniformTexelBufferUpdateAfterBind:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingStorageBufferUpdateAfterBind:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingStorageImageUpdateAfterBind:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingSampledImageUpdateAfterBind:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:descriptorBindingUniformBufferUpdateAfterBind:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderStorageTexelBufferArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderUniformTexelBufferArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderInputAttachmentArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderStorageImageArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderStorageBufferArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderSampledImageArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderUniformBufferArrayNonUniformIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderStorageTexelBufferArrayDynamicIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderUniformTexelBufferArrayDynamicIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
$sel:shaderInputAttachmentArrayDynamicIndexing:PhysicalDeviceDescriptorIndexingFeatures :: PhysicalDeviceDescriptorIndexingFeatures -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
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 PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayDynamicIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayDynamicIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayDynamicIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayNonUniformIndexing))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformBufferUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingSampledImageUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageImageUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageBufferUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformTexelBufferUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageTexelBufferUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUpdateUnusedWhilePending))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingPartiallyBound))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingVariableDescriptorCount))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
runtimeDescriptorArray))
    IO b
f
  cStructSize :: Int
cStructSize = Int
96
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDescriptorIndexingFeatures
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
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 PhysicalDeviceDescriptorIndexingFeatures
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 PhysicalDeviceDescriptorIndexingFeatures
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 PhysicalDeviceDescriptorIndexingFeatures
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 PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceDescriptorIndexingFeatures where
  peekCStruct :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
peekCStruct Ptr PhysicalDeviceDescriptorIndexingFeatures
p = do
    Bool32
shaderInputAttachmentArrayDynamicIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    Bool32
shaderUniformTexelBufferArrayDynamicIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Bool32
shaderStorageTexelBufferArrayDynamicIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    Bool32
shaderUniformBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
    Bool32
shaderUniformTexelBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32))
    Bool32
shaderStorageTexelBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32))
    Bool32
descriptorBindingUniformBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
    Bool32
descriptorBindingSampledImageUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
    Bool32
descriptorBindingStorageImageUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32))
    Bool32
descriptorBindingStorageBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32))
    Bool32
descriptorBindingUniformTexelBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32))
    Bool32
descriptorBindingStorageTexelBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32))
    Bool32
descriptorBindingUpdateUnusedWhilePending <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32))
    Bool32
descriptorBindingPartiallyBound <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32))
    Bool32
descriptorBindingVariableDescriptorCount <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32))
    Bool32
runtimeDescriptorArray <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceDescriptorIndexingFeatures
PhysicalDeviceDescriptorIndexingFeatures
             (Bool32 -> Bool
bool32ToBool Bool32
shaderInputAttachmentArrayDynamicIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderUniformTexelBufferArrayDynamicIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageTexelBufferArrayDynamicIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderUniformBufferArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderSampledImageArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageBufferArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderInputAttachmentArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderUniformTexelBufferArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageTexelBufferArrayNonUniformIndexing)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingUniformBufferUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingSampledImageUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingStorageImageUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingStorageBufferUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingUniformTexelBufferUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingStorageTexelBufferUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingUpdateUnusedWhilePending)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingPartiallyBound)
             (Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingVariableDescriptorCount)
             (Bool32 -> Bool
bool32ToBool Bool32
runtimeDescriptorArray)

instance Storable PhysicalDeviceDescriptorIndexingFeatures where
  sizeOf :: PhysicalDeviceDescriptorIndexingFeatures -> Int
sizeOf ~PhysicalDeviceDescriptorIndexingFeatures
_ = Int
96
  alignment :: PhysicalDeviceDescriptorIndexingFeatures -> Int
alignment ~PhysicalDeviceDescriptorIndexingFeatures
_ = Int
8
  peek :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> IO ()
poke Ptr PhysicalDeviceDescriptorIndexingFeatures
ptr PhysicalDeviceDescriptorIndexingFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingFeatures
ptr PhysicalDeviceDescriptorIndexingFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceDescriptorIndexingFeatures where
  zero :: PhysicalDeviceDescriptorIndexingFeatures
zero = Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceDescriptorIndexingFeatures
PhysicalDeviceDescriptorIndexingFeatures
           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


-- | VkPhysicalDeviceDescriptorIndexingProperties - Structure describing
-- descriptor indexing properties that can be supported by an
-- implementation
--
-- = Description
--
-- If the 'PhysicalDeviceDescriptorIndexingProperties' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_descriptor_indexing VK_EXT_descriptor_indexing>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDescriptorIndexingProperties = PhysicalDeviceDescriptorIndexingProperties
  { -- | #extension-limits-maxUpdateAfterBindDescriptorsInAllPools#
    -- @maxUpdateAfterBindDescriptorsInAllPools@ is the maximum number of
    -- descriptors (summed over all descriptor types) that /can/ be created
    -- across all pools that are created with the
    -- 'Vulkan.Core10.Enums.DescriptorPoolCreateFlagBits.DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT'
    -- bit set. Pool creation /may/ fail when this limit is exceeded, or when
    -- the space this limit represents is unable to satisfy a pool creation due
    -- to fragmentation.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxUpdateAfterBindDescriptorsInAllPools :: Word32
  , -- | #extension-limits-shaderUniformBufferArrayNonUniformIndexingNative#
    -- @shaderUniformBufferArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether uniform buffer descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of uniform buffers /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
shaderUniformBufferArrayNonUniformIndexingNative :: Bool
  , -- | #extension-limits-shaderSampledImageArrayNonUniformIndexingNative#
    -- @shaderSampledImageArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether sampler and image descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of samplers or images /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
shaderSampledImageArrayNonUniformIndexingNative :: Bool
  , -- | #extension-limits-shaderStorageBufferArrayNonUniformIndexingNative#
    -- @shaderStorageBufferArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether storage buffer descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of storage buffers /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
shaderStorageBufferArrayNonUniformIndexingNative :: Bool
  , -- | #extension-limits-shaderStorageImageArrayNonUniformIndexingNative#
    -- @shaderStorageImageArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether storage image descriptors natively support nonuniform
    -- indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE', then a
    -- single dynamic instance of an instruction that nonuniformly indexes an
    -- array of storage images /may/ execute multiple times in order to access
    -- all the descriptors.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
shaderStorageImageArrayNonUniformIndexingNative :: Bool
  , -- | #extension-limits-shaderInputAttachmentArrayNonUniformIndexingNative#
    -- @shaderInputAttachmentArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether input attachment descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of input attachments /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
shaderInputAttachmentArrayNonUniformIndexingNative :: Bool
  , -- | #extension-limits-robustBufferAccessUpdateAfterBind#
    -- @robustBufferAccessUpdateAfterBind@ is a boolean value indicating
    -- whether
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess>
    -- /can/ be enabled on a device simultaneously with
    -- @descriptorBindingUniformBufferUpdateAfterBind@,
    -- @descriptorBindingStorageBufferUpdateAfterBind@,
    -- @descriptorBindingUniformTexelBufferUpdateAfterBind@, and\/or
    -- @descriptorBindingStorageTexelBufferUpdateAfterBind@. If this is
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', then either @robustBufferAccess@
    -- /must/ be disabled or all of these update-after-bind features /must/ be
    -- disabled.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
robustBufferAccessUpdateAfterBind :: Bool
  , -- | #extension-limits-quadDivergentImplicitLod# @quadDivergentImplicitLod@
    -- is a boolean value indicating whether implicit LOD calculations for
    -- image operations have well-defined results when the image and\/or
    -- sampler objects used for the instruction are not uniform within a quad.
    -- See
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-derivative-image-operations Derivative Image Operations>.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
quadDivergentImplicitLod :: Bool
  , -- | #extension-limits-maxPerStageDescriptorUpdateAfterBindSamplers#
    -- @maxPerStageDescriptorUpdateAfterBindSamplers@ is similar to
    -- @maxPerStageDescriptorSamplers@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageDescriptorUpdateAfterBindSamplers :: Word32
  , -- | #extension-limits-maxPerStageDescriptorUpdateAfterBindUniformBuffers#
    -- @maxPerStageDescriptorUpdateAfterBindUniformBuffers@ is similar to
    -- @maxPerStageDescriptorUniformBuffers@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers :: Word32
  , -- | #extension-limits-maxPerStageDescriptorUpdateAfterBindStorageBuffers#
    -- @maxPerStageDescriptorUpdateAfterBindStorageBuffers@ is similar to
    -- @maxPerStageDescriptorStorageBuffers@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers :: Word32
  , -- | #extension-limits-maxPerStageDescriptorUpdateAfterBindSampledImages#
    -- @maxPerStageDescriptorUpdateAfterBindSampledImages@ is similar to
    -- @maxPerStageDescriptorSampledImages@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageDescriptorUpdateAfterBindSampledImages :: Word32
  , -- | #extension-limits-maxPerStageDescriptorUpdateAfterBindStorageImages#
    -- @maxPerStageDescriptorUpdateAfterBindStorageImages@ is similar to
    -- @maxPerStageDescriptorStorageImages@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageDescriptorUpdateAfterBindStorageImages :: Word32
  , -- | #extension-limits-maxPerStageDescriptorUpdateAfterBindInputAttachments#
    -- @maxPerStageDescriptorUpdateAfterBindInputAttachments@ is similar to
    -- @maxPerStageDescriptorInputAttachments@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments :: Word32
  , -- | #extension-limits-maxPerStageUpdateAfterBindResources#
    -- @maxPerStageUpdateAfterBindResources@ is similar to
    -- @maxPerStageResources@ but counts descriptors from descriptor sets
    -- created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxPerStageUpdateAfterBindResources :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindSamplers#
    -- @maxDescriptorSetUpdateAfterBindSamplers@ is similar to
    -- @maxDescriptorSetSamplers@ but counts descriptors from descriptor sets
    -- created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindSamplers :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindUniformBuffers#
    -- @maxDescriptorSetUpdateAfterBindUniformBuffers@ is similar to
    -- @maxDescriptorSetUniformBuffers@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffers :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindUniformBuffersDynamic#
    -- @maxDescriptorSetUpdateAfterBindUniformBuffersDynamic@ is similar to
    -- @maxDescriptorSetUniformBuffersDynamic@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set. While an application /can/ allocate dynamic uniform buffer
    -- descriptors from a pool created with the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT',
    -- bindings for these descriptors /must/ not be present in any descriptor
    -- set layout that includes bindings created with
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindStorageBuffers#
    -- @maxDescriptorSetUpdateAfterBindStorageBuffers@ is similar to
    -- @maxDescriptorSetStorageBuffers@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffers :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindStorageBuffersDynamic#
    -- @maxDescriptorSetUpdateAfterBindStorageBuffersDynamic@ is similar to
    -- @maxDescriptorSetStorageBuffersDynamic@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set. While an application /can/ allocate dynamic storage buffer
    -- descriptors from a pool created with the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT',
    -- bindings for these descriptors /must/ not be present in any descriptor
    -- set layout that includes bindings created with
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindSampledImages#
    -- @maxDescriptorSetUpdateAfterBindSampledImages@ is similar to
    -- @maxDescriptorSetSampledImages@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindSampledImages :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindStorageImages#
    -- @maxDescriptorSetUpdateAfterBindStorageImages@ is similar to
    -- @maxDescriptorSetStorageImages@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindStorageImages :: Word32
  , -- | #extension-limits-maxDescriptorSetUpdateAfterBindInputAttachments#
    -- @maxDescriptorSetUpdateAfterBindInputAttachments@ is similar to
    -- @maxDescriptorSetInputAttachments@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindInputAttachments :: Word32
  }
  deriving (Typeable, PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> Bool
$c/= :: PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> Bool
== :: PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> Bool
$c== :: PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDescriptorIndexingProperties)
#endif
deriving instance Show PhysicalDeviceDescriptorIndexingProperties

instance ToCStruct PhysicalDeviceDescriptorIndexingProperties where
  withCStruct :: forall b.
PhysicalDeviceDescriptorIndexingProperties
-> (Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b) -> IO b
withCStruct PhysicalDeviceDescriptorIndexingProperties
x Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
112 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDescriptorIndexingProperties
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingProperties
p PhysicalDeviceDescriptorIndexingProperties
x (Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b
f Ptr PhysicalDeviceDescriptorIndexingProperties
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingProperties
p PhysicalDeviceDescriptorIndexingProperties{Bool
Word32
maxDescriptorSetUpdateAfterBindInputAttachments :: Word32
maxDescriptorSetUpdateAfterBindStorageImages :: Word32
maxDescriptorSetUpdateAfterBindSampledImages :: Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic :: Word32
maxDescriptorSetUpdateAfterBindStorageBuffers :: Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic :: Word32
maxDescriptorSetUpdateAfterBindUniformBuffers :: Word32
maxDescriptorSetUpdateAfterBindSamplers :: Word32
maxPerStageUpdateAfterBindResources :: Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments :: Word32
maxPerStageDescriptorUpdateAfterBindStorageImages :: Word32
maxPerStageDescriptorUpdateAfterBindSampledImages :: Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers :: Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers :: Word32
maxPerStageDescriptorUpdateAfterBindSamplers :: Word32
quadDivergentImplicitLod :: Bool
robustBufferAccessUpdateAfterBind :: Bool
shaderInputAttachmentArrayNonUniformIndexingNative :: Bool
shaderStorageImageArrayNonUniformIndexingNative :: Bool
shaderStorageBufferArrayNonUniformIndexingNative :: Bool
shaderSampledImageArrayNonUniformIndexingNative :: Bool
shaderUniformBufferArrayNonUniformIndexingNative :: Bool
maxUpdateAfterBindDescriptorsInAllPools :: Word32
$sel:maxDescriptorSetUpdateAfterBindInputAttachments:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindStorageImages:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindSampledImages:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindStorageBuffersDynamic:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindStorageBuffers:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindUniformBuffersDynamic:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindUniformBuffers:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxDescriptorSetUpdateAfterBindSamplers:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageUpdateAfterBindResources:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindInputAttachments:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindStorageImages:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindSampledImages:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindStorageBuffers:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindUniformBuffers:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindSamplers:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
$sel:quadDivergentImplicitLod:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:robustBufferAccessUpdateAfterBind:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:shaderInputAttachmentArrayNonUniformIndexingNative:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:shaderStorageImageArrayNonUniformIndexingNative:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:shaderStorageBufferArrayNonUniformIndexingNative:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:shaderSampledImageArrayNonUniformIndexingNative:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:shaderUniformBufferArrayNonUniformIndexingNative:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Bool
$sel:maxUpdateAfterBindDescriptorsInAllPools:PhysicalDeviceDescriptorIndexingProperties :: PhysicalDeviceDescriptorIndexingProperties -> Word32
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
maxUpdateAfterBindDescriptorsInAllPools)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexingNative))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexingNative))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexingNative))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexingNative))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexingNative))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccessUpdateAfterBind))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
quadDivergentImplicitLod))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSamplers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSampledImages)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageImages)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Word32)) (Word32
maxPerStageUpdateAfterBindResources)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSamplers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSampledImages)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageImages)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindInputAttachments)
    IO b
f
  cStructSize :: Int
cStructSize = Int
112
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDescriptorIndexingProperties
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
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 PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceDescriptorIndexingProperties where
  peekCStruct :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
peekCStruct Ptr PhysicalDeviceDescriptorIndexingProperties
p = do
    Word32
maxUpdateAfterBindDescriptorsInAllPools <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Bool32
shaderUniformBufferArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
    Bool32
robustBufferAccessUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
    Bool32
quadDivergentImplicitLod <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
    Word32
maxPerStageDescriptorUpdateAfterBindSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindSampledImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindStorageImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Word32))
    Word32
maxPerStageUpdateAfterBindResources <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindUniformBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindSampledImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindInputAttachments <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Word32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDeviceDescriptorIndexingProperties
PhysicalDeviceDescriptorIndexingProperties
             Word32
maxUpdateAfterBindDescriptorsInAllPools
             (Bool32 -> Bool
bool32ToBool Bool32
shaderUniformBufferArrayNonUniformIndexingNative)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderSampledImageArrayNonUniformIndexingNative)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageBufferArrayNonUniformIndexingNative)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageArrayNonUniformIndexingNative)
             (Bool32 -> Bool
bool32ToBool Bool32
shaderInputAttachmentArrayNonUniformIndexingNative)
             (Bool32 -> Bool
bool32ToBool Bool32
robustBufferAccessUpdateAfterBind)
             (Bool32 -> Bool
bool32ToBool Bool32
quadDivergentImplicitLod)
             Word32
maxPerStageDescriptorUpdateAfterBindSamplers
             Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers
             Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers
             Word32
maxPerStageDescriptorUpdateAfterBindSampledImages
             Word32
maxPerStageDescriptorUpdateAfterBindStorageImages
             Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments
             Word32
maxPerStageUpdateAfterBindResources
             Word32
maxDescriptorSetUpdateAfterBindSamplers
             Word32
maxDescriptorSetUpdateAfterBindUniformBuffers
             Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic
             Word32
maxDescriptorSetUpdateAfterBindStorageBuffers
             Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic
             Word32
maxDescriptorSetUpdateAfterBindSampledImages
             Word32
maxDescriptorSetUpdateAfterBindStorageImages
             Word32
maxDescriptorSetUpdateAfterBindInputAttachments

instance Storable PhysicalDeviceDescriptorIndexingProperties where
  sizeOf :: PhysicalDeviceDescriptorIndexingProperties -> Int
sizeOf ~PhysicalDeviceDescriptorIndexingProperties
_ = Int
112
  alignment :: PhysicalDeviceDescriptorIndexingProperties -> Int
alignment ~PhysicalDeviceDescriptorIndexingProperties
_ = Int
8
  peek :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> IO ()
poke Ptr PhysicalDeviceDescriptorIndexingProperties
ptr PhysicalDeviceDescriptorIndexingProperties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingProperties
ptr PhysicalDeviceDescriptorIndexingProperties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceDescriptorIndexingProperties where
  zero :: PhysicalDeviceDescriptorIndexingProperties
zero = Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDeviceDescriptorIndexingProperties
PhysicalDeviceDescriptorIndexingProperties
           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


-- | VkDescriptorSetLayoutBindingFlagsCreateInfo - Structure specifying
-- creation flags for descriptor set layout bindings
--
-- = Description
--
-- If @bindingCount@ is zero or if this structure is not included in the
-- @pNext@ chain, the
-- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DescriptorBindingFlags'
-- for each descriptor set layout binding is considered to be zero.
-- Otherwise, the descriptor set layout binding at
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo'::@pBindings@[i]
-- uses the flags in @pBindingFlags@[i].
--
-- == Valid Usage
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-bindingCount-03002#
--     If @bindingCount@ is not zero, @bindingCount@ /must/ equal
--     'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo'::@bindingCount@
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-flags-03003# If
--     'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo'::@flags@
--     includes
--     'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR',
--     then all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT',
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT',
--     or
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-pBindingFlags-03004#
--     If an element of @pBindingFlags@ includes
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT',
--     then all other elements of
--     'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo'::@pBindings@
--     /must/ have a smaller value of @binding@
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-pBindingFlags-09379#
--     If an element of @pBindingFlags@ includes
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT',
--     then it /must/ be the element with the the highest @binding@ number
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingUniformBufferUpdateAfterBind-03005#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingUniformBufferUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingSampledImageUpdateAfterBind-03006#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingSampledImageUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER',
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingStorageImageUpdateAfterBind-03007#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingStorageImageUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingStorageBufferUpdateAfterBind-03008#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingStorageBufferUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingUniformTexelBufferUpdateAfterBind-03009#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingUniformTexelBufferUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingStorageTexelBufferUpdateAfterBind-03010#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingStorageTexelBufferUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingInlineUniformBlockUpdateAfterBind-02211#
--     If
--     'Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockFeatures'::@descriptorBindingInlineUniformBlockUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingAccelerationStructureUpdateAfterBind-03570#
--     If
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.PhysicalDeviceAccelerationStructureFeaturesKHR'::@descriptorBindingAccelerationStructureUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR'
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-None-03011# All
--     bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT',
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC',
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingUpdateUnusedWhilePending-03012#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingUpdateUnusedWhilePending@
--     is not enabled, all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingPartiallyBound-03013#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingPartiallyBound@
--     is not enabled, all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_PARTIALLY_BOUND_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-descriptorBindingVariableDescriptorCount-03014#
--     If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingVariableDescriptorCount@
--     is not enabled, all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-pBindingFlags-03015#
--     If an element of @pBindingFlags@ includes
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT',
--     that element’s @descriptorType@ /must/ not be
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO'
--
-- -   #VUID-VkDescriptorSetLayoutBindingFlagsCreateInfo-pBindingFlags-parameter#
--     If @bindingCount@ is not @0@, @pBindingFlags@ /must/ be a valid
--     pointer to an array of @bindingCount@ valid combinations of
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DescriptorBindingFlagBits'
--     values
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_descriptor_indexing VK_EXT_descriptor_indexing>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DescriptorBindingFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DescriptorSetLayoutBindingFlagsCreateInfo = DescriptorSetLayoutBindingFlagsCreateInfo
  { -- | @pBindingFlags@ is a pointer to an array of
    -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DescriptorBindingFlags'
    -- bitfields, one for each descriptor set layout binding.
    DescriptorSetLayoutBindingFlagsCreateInfo
-> Vector DescriptorBindingFlags
bindingFlags :: Vector DescriptorBindingFlags }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorSetLayoutBindingFlagsCreateInfo)
#endif
deriving instance Show DescriptorSetLayoutBindingFlagsCreateInfo

instance ToCStruct DescriptorSetLayoutBindingFlagsCreateInfo where
  withCStruct :: forall b.
DescriptorSetLayoutBindingFlagsCreateInfo
-> (Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b) -> IO b
withCStruct DescriptorSetLayoutBindingFlagsCreateInfo
x Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p DescriptorSetLayoutBindingFlagsCreateInfo
x (Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b
f Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p)
  pokeCStruct :: forall b.
Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> DescriptorSetLayoutBindingFlagsCreateInfo -> IO b -> IO b
pokeCStruct Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p DescriptorSetLayoutBindingFlagsCreateInfo{Vector DescriptorBindingFlags
bindingFlags :: Vector DescriptorBindingFlags
$sel:bindingFlags:DescriptorSetLayoutBindingFlagsCreateInfo :: DescriptorSetLayoutBindingFlagsCreateInfo
-> Vector DescriptorBindingFlags
..} 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 DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO)
    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 DescriptorSetLayoutBindingFlagsCreateInfo
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 ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector DescriptorBindingFlags
bindingFlags)) :: Word32))
    Ptr DescriptorBindingFlags
pPBindingFlags' <- 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 @DescriptorBindingFlags ((forall a. Vector a -> Int
Data.Vector.length (Vector DescriptorBindingFlags
bindingFlags)) 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 DescriptorBindingFlags
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DescriptorBindingFlags
pPBindingFlags' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorBindingFlags) (DescriptorBindingFlags
e)) (Vector DescriptorBindingFlags
bindingFlags)
    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 DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr DescriptorBindingFlags))) (Ptr DescriptorBindingFlags
pPBindingFlags')
    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 DescriptorSetLayoutBindingFlagsCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct DescriptorSetLayoutBindingFlagsCreateInfo where
  peekCStruct :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> IO DescriptorSetLayoutBindingFlagsCreateInfo
peekCStruct Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p = do
    Word32
bindingCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Ptr DescriptorBindingFlags
pBindingFlags <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorBindingFlags) ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr DescriptorBindingFlags)))
    Vector DescriptorBindingFlags
pBindingFlags' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
bindingCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @DescriptorBindingFlags ((Ptr DescriptorBindingFlags
pBindingFlags forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorBindingFlags)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector DescriptorBindingFlags
-> DescriptorSetLayoutBindingFlagsCreateInfo
DescriptorSetLayoutBindingFlagsCreateInfo
             Vector DescriptorBindingFlags
pBindingFlags'

instance Zero DescriptorSetLayoutBindingFlagsCreateInfo where
  zero :: DescriptorSetLayoutBindingFlagsCreateInfo
zero = Vector DescriptorBindingFlags
-> DescriptorSetLayoutBindingFlagsCreateInfo
DescriptorSetLayoutBindingFlagsCreateInfo
           forall a. Monoid a => a
mempty


-- | VkDescriptorSetVariableDescriptorCountAllocateInfo - Structure
-- specifying additional allocation parameters for descriptor sets
--
-- = Description
--
-- If @descriptorSetCount@ is zero or this structure is not included in the
-- @pNext@ chain, then the variable lengths are considered to be zero.
-- Otherwise, @pDescriptorCounts@[i] is the number of descriptors in the
-- variable-sized descriptor binding in the corresponding descriptor set
-- layout. If the variable-sized descriptor binding in the corresponding
-- descriptor set layout has a descriptor type of
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK'
-- then @pDescriptorCounts@[i] specifies the binding’s capacity in bytes.
-- If
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo'::@pSetLayouts@[i]
-- does not include a variable-sized descriptor binding, then
-- @pDescriptorCounts@[i] is ignored.
--
-- == Valid Usage
--
-- -   #VUID-VkDescriptorSetVariableDescriptorCountAllocateInfo-descriptorSetCount-03045#
--     If @descriptorSetCount@ is not zero, @descriptorSetCount@ /must/
--     equal
--     'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo'::@descriptorSetCount@
--
-- -   #VUID-VkDescriptorSetVariableDescriptorCountAllocateInfo-pSetLayouts-03046#
--     If
--     'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo'::@pSetLayouts@[i]
--     has a variable-sized descriptor binding, then @pDescriptorCounts@[i]
--     /must/ be less than or equal to the descriptor count specified for
--     that binding when the descriptor set layout was created
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkDescriptorSetVariableDescriptorCountAllocateInfo-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO'
--
-- -   #VUID-VkDescriptorSetVariableDescriptorCountAllocateInfo-pDescriptorCounts-parameter#
--     If @descriptorSetCount@ is not @0@, @pDescriptorCounts@ /must/ be a
--     valid pointer to an array of @descriptorSetCount@ @uint32_t@ values
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_descriptor_indexing VK_EXT_descriptor_indexing>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DescriptorSetVariableDescriptorCountAllocateInfo = DescriptorSetVariableDescriptorCountAllocateInfo
  { -- | @pDescriptorCounts@ is a pointer to an array of descriptor counts, with
    -- each member specifying the number of descriptors in a variable-sized
    -- descriptor binding in the corresponding descriptor set being allocated.
    DescriptorSetVariableDescriptorCountAllocateInfo -> Vector Word32
descriptorCounts :: Vector Word32 }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorSetVariableDescriptorCountAllocateInfo)
#endif
deriving instance Show DescriptorSetVariableDescriptorCountAllocateInfo

instance ToCStruct DescriptorSetVariableDescriptorCountAllocateInfo where
  withCStruct :: forall b.
DescriptorSetVariableDescriptorCountAllocateInfo
-> (Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b)
-> IO b
withCStruct DescriptorSetVariableDescriptorCountAllocateInfo
x Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p DescriptorSetVariableDescriptorCountAllocateInfo
x (Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b
f Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p)
  pokeCStruct :: forall b.
Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> DescriptorSetVariableDescriptorCountAllocateInfo -> IO b -> IO b
pokeCStruct Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p DescriptorSetVariableDescriptorCountAllocateInfo{Vector Word32
descriptorCounts :: Vector Word32
$sel:descriptorCounts:DescriptorSetVariableDescriptorCountAllocateInfo :: DescriptorSetVariableDescriptorCountAllocateInfo -> Vector Word32
..} 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 DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO)
    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 DescriptorSetVariableDescriptorCountAllocateInfo
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 ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Word32
descriptorCounts)) :: Word32))
    Ptr Word32
pPDescriptorCounts' <- 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 (Vector Word32
descriptorCounts)) 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 Word32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPDescriptorCounts' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
descriptorCounts)
    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 DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Word32))) (Ptr Word32
pPDescriptorCounts')
    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 DescriptorSetVariableDescriptorCountAllocateInfo
-> IO b -> IO b
pokeZeroCStruct Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct DescriptorSetVariableDescriptorCountAllocateInfo where
  peekCStruct :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> IO DescriptorSetVariableDescriptorCountAllocateInfo
peekCStruct Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p = do
    Word32
descriptorSetCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Ptr Word32
pDescriptorCounts <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Word32)))
    Vector Word32
pDescriptorCounts' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
descriptorSetCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pDescriptorCounts forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector Word32 -> DescriptorSetVariableDescriptorCountAllocateInfo
DescriptorSetVariableDescriptorCountAllocateInfo
             Vector Word32
pDescriptorCounts'

instance Zero DescriptorSetVariableDescriptorCountAllocateInfo where
  zero :: DescriptorSetVariableDescriptorCountAllocateInfo
zero = Vector Word32 -> DescriptorSetVariableDescriptorCountAllocateInfo
DescriptorSetVariableDescriptorCountAllocateInfo
           forall a. Monoid a => a
mempty


-- | VkDescriptorSetVariableDescriptorCountLayoutSupport - Structure
-- returning information about whether a descriptor set layout can be
-- supported
--
-- = Description
--
-- If the 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo'
-- structure specified in
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.getDescriptorSetLayoutSupport'::@pCreateInfo@
-- includes a variable-sized descriptor, then @supported@ is determined
-- assuming the requested size of the variable-sized descriptor, and
-- @maxVariableDescriptorCount@ is set to the maximum size of that
-- descriptor that /can/ be successfully created (which is greater than or
-- equal to the requested size passed in). If the
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo' structure
-- does not include a variable-sized descriptor, or if the
-- 'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingVariableDescriptorCount@
-- feature is not enabled, then @maxVariableDescriptorCount@ is set to
-- zero. For the purposes of this command, a variable-sized descriptor
-- binding with a @descriptorCount@ of zero is treated as having a
-- @descriptorCount@ of four if @descriptorType@ is
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK',
-- or one otherwise, and thus the binding is not ignored and the maximum
-- descriptor count will be returned. If the layout is not supported, then
-- the value written to @maxVariableDescriptorCount@ is undefined.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_descriptor_indexing VK_EXT_descriptor_indexing>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DescriptorSetVariableDescriptorCountLayoutSupport = DescriptorSetVariableDescriptorCountLayoutSupport
  { -- | @maxVariableDescriptorCount@ indicates the maximum number of descriptors
    -- supported in the highest numbered binding of the layout, if that binding
    -- is variable-sized. If the highest numbered binding of the layout has a
    -- descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK'
    -- then @maxVariableDescriptorCount@ indicates the maximum byte size
    -- supported for the binding, if that binding is variable-sized.
    DescriptorSetVariableDescriptorCountLayoutSupport -> Word32
maxVariableDescriptorCount :: Word32 }
  deriving (Typeable, DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool
$c/= :: DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool
== :: DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool
$c== :: DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorSetVariableDescriptorCountLayoutSupport)
#endif
deriving instance Show DescriptorSetVariableDescriptorCountLayoutSupport

instance ToCStruct DescriptorSetVariableDescriptorCountLayoutSupport where
  withCStruct :: forall b.
DescriptorSetVariableDescriptorCountLayoutSupport
-> (Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b)
-> IO b
withCStruct DescriptorSetVariableDescriptorCountLayoutSupport
x Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p DescriptorSetVariableDescriptorCountLayoutSupport
x (Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b
f Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p)
  pokeCStruct :: forall b.
Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport
-> IO b
-> IO b
pokeCStruct Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p DescriptorSetVariableDescriptorCountLayoutSupport{Word32
maxVariableDescriptorCount :: Word32
$sel:maxVariableDescriptorCount:DescriptorSetVariableDescriptorCountLayoutSupport :: DescriptorSetVariableDescriptorCountLayoutSupport -> Word32
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
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 DescriptorSetVariableDescriptorCountLayoutSupport
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
maxVariableDescriptorCount)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> IO b -> IO b
pokeZeroCStruct Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
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 DescriptorSetVariableDescriptorCountLayoutSupport
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DescriptorSetVariableDescriptorCountLayoutSupport where
  peekCStruct :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> IO DescriptorSetVariableDescriptorCountLayoutSupport
peekCStruct Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p = do
    Word32
maxVariableDescriptorCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> DescriptorSetVariableDescriptorCountLayoutSupport
DescriptorSetVariableDescriptorCountLayoutSupport
             Word32
maxVariableDescriptorCount

instance Storable DescriptorSetVariableDescriptorCountLayoutSupport where
  sizeOf :: DescriptorSetVariableDescriptorCountLayoutSupport -> Int
sizeOf ~DescriptorSetVariableDescriptorCountLayoutSupport
_ = Int
24
  alignment :: DescriptorSetVariableDescriptorCountLayoutSupport -> Int
alignment ~DescriptorSetVariableDescriptorCountLayoutSupport
_ = Int
8
  peek :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> IO DescriptorSetVariableDescriptorCountLayoutSupport
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport -> IO ()
poke Ptr DescriptorSetVariableDescriptorCountLayoutSupport
ptr DescriptorSetVariableDescriptorCountLayoutSupport
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DescriptorSetVariableDescriptorCountLayoutSupport
ptr DescriptorSetVariableDescriptorCountLayoutSupport
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero DescriptorSetVariableDescriptorCountLayoutSupport where
  zero :: DescriptorSetVariableDescriptorCountLayoutSupport
zero = Word32 -> DescriptorSetVariableDescriptorCountLayoutSupport
DescriptorSetVariableDescriptorCountLayoutSupport
           forall a. Zero a => a
zero