{-# language CPP #-}
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 (allocaBytesAligned)
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 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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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
--
-- The members of the 'PhysicalDeviceDescriptorIndexingFeatures' structure
-- describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceDescriptorIndexingFeatures' structure is included
-- in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether each feature is supported.
-- 'PhysicalDeviceDescriptorIndexingFeatures' /can/ also be included in the
-- @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDescriptorIndexingFeatures = PhysicalDeviceDescriptorIndexingFeatures
  { -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
(PhysicalDeviceDescriptorIndexingFeatures
 -> PhysicalDeviceDescriptorIndexingFeatures -> Bool)
-> (PhysicalDeviceDescriptorIndexingFeatures
    -> PhysicalDeviceDescriptorIndexingFeatures -> Bool)
-> Eq PhysicalDeviceDescriptorIndexingFeatures
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 :: PhysicalDeviceDescriptorIndexingFeatures
-> (Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b) -> IO b
withCStruct x :: PhysicalDeviceDescriptorIndexingFeatures
x f :: Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 96 8 ((Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceDescriptorIndexingFeatures
p -> Ptr PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> IO b -> IO b
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 :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceDescriptorIndexingFeatures
p PhysicalDeviceDescriptorIndexingFeatures{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingSampledImageUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageImageUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformTexelBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageTexelBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUpdateUnusedWhilePending))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingPartiallyBound))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingVariableDescriptorCount))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
runtimeDescriptorArray))
    IO b
f
  cStructSize :: Int
cStructSize = 96
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceDescriptorIndexingFeatures -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceDescriptorIndexingFeatures
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceDescriptorIndexingFeatures where
  peekCStruct :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
peekCStruct p :: Ptr PhysicalDeviceDescriptorIndexingFeatures
p = do
    Bool32
shaderInputAttachmentArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
shaderUniformTexelBufferArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
shaderStorageTexelBufferArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
shaderUniformBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    Bool32
shaderUniformTexelBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32))
    Bool32
shaderStorageTexelBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32))
    Bool32
descriptorBindingUniformBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32))
    Bool32
descriptorBindingSampledImageUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32))
    Bool32
descriptorBindingStorageImageUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32))
    Bool32
descriptorBindingStorageBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32))
    Bool32
descriptorBindingUniformTexelBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32))
    Bool32
descriptorBindingStorageTexelBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32))
    Bool32
descriptorBindingUpdateUnusedWhilePending <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32))
    Bool32
descriptorBindingPartiallyBound <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32))
    Bool32
descriptorBindingVariableDescriptorCount <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32))
    Bool32
runtimeDescriptorArray <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingFeatures
p Ptr PhysicalDeviceDescriptorIndexingFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32))
    PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDescriptorIndexingFeatures
 -> IO PhysicalDeviceDescriptorIndexingFeatures)
-> PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
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
_ = 96
  alignment :: PhysicalDeviceDescriptorIndexingFeatures -> Int
alignment ~PhysicalDeviceDescriptorIndexingFeatures
_ = 8
  peek :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
peek = Ptr PhysicalDeviceDescriptorIndexingFeatures
-> IO PhysicalDeviceDescriptorIndexingFeatures
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> IO ()
poke ptr :: Ptr PhysicalDeviceDescriptorIndexingFeatures
ptr poked :: PhysicalDeviceDescriptorIndexingFeatures
poked = Ptr PhysicalDeviceDescriptorIndexingFeatures
-> PhysicalDeviceDescriptorIndexingFeatures -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingFeatures
ptr PhysicalDeviceDescriptorIndexingFeatures
poked (() -> IO ()
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
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceDescriptorIndexingProperties - Structure describing
-- descriptor indexing properties that can be supported by an
-- implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceDescriptorIndexingProperties'
-- structure describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceDescriptorIndexingProperties' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDescriptorIndexingProperties = PhysicalDeviceDescriptorIndexingProperties
  { -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @robustBufferAccessUpdateAfterBind@ is a boolean value indicating
    -- whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess>
    -- /can/ be enabled in 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
  , -- | @quadDivergentImplicitLod@ is a boolean value indicating whether
    -- implicit level of detail 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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-derivative-image-operations Derivative Image Operations>.
    PhysicalDeviceDescriptorIndexingProperties -> Bool
quadDivergentImplicitLod :: Bool
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic :: Word32
  , -- | @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
  , -- | @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.
    PhysicalDeviceDescriptorIndexingProperties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic :: Word32
  , -- | @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
  , -- | @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
  , -- | @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
(PhysicalDeviceDescriptorIndexingProperties
 -> PhysicalDeviceDescriptorIndexingProperties -> Bool)
-> (PhysicalDeviceDescriptorIndexingProperties
    -> PhysicalDeviceDescriptorIndexingProperties -> Bool)
-> Eq PhysicalDeviceDescriptorIndexingProperties
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 :: PhysicalDeviceDescriptorIndexingProperties
-> (Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b) -> IO b
withCStruct x :: PhysicalDeviceDescriptorIndexingProperties
x f :: Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 112 8 ((Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceDescriptorIndexingProperties
p -> Ptr PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> IO b -> IO b
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 :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceDescriptorIndexingProperties
p PhysicalDeviceDescriptorIndexingProperties{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
maxUpdateAfterBindDescriptorsInAllPools)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexingNative))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexingNative))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexingNative))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexingNative))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexingNative))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccessUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
quadDivergentImplicitLod))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSamplers)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSampledImages)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageImages)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) (Word32
maxPerStageUpdateAfterBindResources)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSamplers)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffers)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffers)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSampledImages)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageImages)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindInputAttachments)
    IO b
f
  cStructSize :: Int
cStructSize = 112
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceDescriptorIndexingProperties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceDescriptorIndexingProperties
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceDescriptorIndexingProperties where
  peekCStruct :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
peekCStruct p :: Ptr PhysicalDeviceDescriptorIndexingProperties
p = do
    Word32
maxUpdateAfterBindDescriptorsInAllPools <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Bool32
shaderUniformBufferArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    Bool32
robustBufferAccessUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
quadDivergentImplicitLod <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    Word32
maxPerStageDescriptorUpdateAfterBindSamplers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindSampledImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindStorageImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32))
    Word32
maxPerStageUpdateAfterBindResources <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindSamplers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindUniformBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindSampledImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindInputAttachments <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDescriptorIndexingProperties
p Ptr PhysicalDeviceDescriptorIndexingProperties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Word32))
    PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDescriptorIndexingProperties
 -> IO PhysicalDeviceDescriptorIndexingProperties)
-> PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
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
_ = 112
  alignment :: PhysicalDeviceDescriptorIndexingProperties -> Int
alignment ~PhysicalDeviceDescriptorIndexingProperties
_ = 8
  peek :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
peek = Ptr PhysicalDeviceDescriptorIndexingProperties
-> IO PhysicalDeviceDescriptorIndexingProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> IO ()
poke ptr :: Ptr PhysicalDeviceDescriptorIndexingProperties
ptr poked :: PhysicalDeviceDescriptorIndexingProperties
poked = Ptr PhysicalDeviceDescriptorIndexingProperties
-> PhysicalDeviceDescriptorIndexingProperties -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorIndexingProperties
ptr PhysicalDeviceDescriptorIndexingProperties
poked (() -> IO ()
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
           Word32
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
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
--
-- -   If @bindingCount@ is not zero, @bindingCount@ /must/ equal
--     'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo'::@bindingCount@
--
-- -   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'
--
-- -   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@
--
-- -   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'
--
-- -   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'
--
-- -   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'
--
-- -   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'
--
-- -   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'
--
-- -   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'
--
-- -   If
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockFeaturesEXT'::@descriptorBindingInlineUniformBlockUpdateAfterBind@
--     is not enabled, all bindings with descriptor type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT'
--     /must/ not use
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--
-- -   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'
--
-- -   If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingUpdateUnusedWhilePending@
--     is not enabled, all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT'
--
-- -   If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingPartiallyBound@
--     is not enabled, all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_PARTIALLY_BOUND_BIT'
--
-- -   If
--     'PhysicalDeviceDescriptorIndexingFeatures'::@descriptorBindingVariableDescriptorCount@
--     is not enabled, all elements of @pBindingFlags@ /must/ not include
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT'
--
-- -   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)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO'
--
-- -   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
--
-- '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 :: DescriptorSetLayoutBindingFlagsCreateInfo
-> (Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b) -> IO b
withCStruct x :: DescriptorSetLayoutBindingFlagsCreateInfo
x f :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b
f = Int
-> Int
-> (Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b) -> IO b)
-> (Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p -> Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> DescriptorSetLayoutBindingFlagsCreateInfo -> IO b -> IO b
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 :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> DescriptorSetLayoutBindingFlagsCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p DescriptorSetLayoutBindingFlagsCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector DescriptorBindingFlags -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DescriptorBindingFlags -> Int)
-> Vector DescriptorBindingFlags -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DescriptorBindingFlags
bindingFlags)) :: Word32))
    Ptr DescriptorBindingFlags
pPBindingFlags' <- ((Ptr DescriptorBindingFlags -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorBindingFlags)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DescriptorBindingFlags -> IO b) -> IO b)
 -> ContT b IO (Ptr DescriptorBindingFlags))
-> ((Ptr DescriptorBindingFlags -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorBindingFlags)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DescriptorBindingFlags -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DescriptorBindingFlags ((Vector DescriptorBindingFlags -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DescriptorBindingFlags
bindingFlags)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DescriptorBindingFlags -> IO ())
-> Vector DescriptorBindingFlags -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DescriptorBindingFlags
e -> Ptr DescriptorBindingFlags -> DescriptorBindingFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DescriptorBindingFlags
pPBindingFlags' Ptr DescriptorBindingFlags -> Int -> Ptr DescriptorBindingFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorBindingFlags) (DescriptorBindingFlags
e)) (Vector DescriptorBindingFlags
bindingFlags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DescriptorBindingFlags)
-> Ptr DescriptorBindingFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr (Ptr DescriptorBindingFlags)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DescriptorBindingFlags))) (Ptr DescriptorBindingFlags
pPBindingFlags')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DescriptorBindingFlags
pPBindingFlags' <- ((Ptr DescriptorBindingFlags -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorBindingFlags)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DescriptorBindingFlags -> IO b) -> IO b)
 -> ContT b IO (Ptr DescriptorBindingFlags))
-> ((Ptr DescriptorBindingFlags -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorBindingFlags)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DescriptorBindingFlags -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DescriptorBindingFlags ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DescriptorBindingFlags -> IO ())
-> Vector DescriptorBindingFlags -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DescriptorBindingFlags
e -> Ptr DescriptorBindingFlags -> DescriptorBindingFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DescriptorBindingFlags
pPBindingFlags' Ptr DescriptorBindingFlags -> Int -> Ptr DescriptorBindingFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorBindingFlags) (DescriptorBindingFlags
e)) (Vector DescriptorBindingFlags
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DescriptorBindingFlags)
-> Ptr DescriptorBindingFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr (Ptr DescriptorBindingFlags)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DescriptorBindingFlags))) (Ptr DescriptorBindingFlags
pPBindingFlags')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct DescriptorSetLayoutBindingFlagsCreateInfo where
  peekCStruct :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> IO DescriptorSetLayoutBindingFlagsCreateInfo
peekCStruct p :: Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p = do
    Word32
bindingCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Ptr DescriptorBindingFlags
pBindingFlags <- Ptr (Ptr DescriptorBindingFlags) -> IO (Ptr DescriptorBindingFlags)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorBindingFlags) ((Ptr DescriptorSetLayoutBindingFlagsCreateInfo
p Ptr DescriptorSetLayoutBindingFlagsCreateInfo
-> Int -> Ptr (Ptr DescriptorBindingFlags)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DescriptorBindingFlags)))
    Vector DescriptorBindingFlags
pBindingFlags' <- Int
-> (Int -> IO DescriptorBindingFlags)
-> IO (Vector DescriptorBindingFlags)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
bindingCount) (\i :: Int
i -> Ptr DescriptorBindingFlags -> IO DescriptorBindingFlags
forall a. Storable a => Ptr a -> IO a
peek @DescriptorBindingFlags ((Ptr DescriptorBindingFlags
pBindingFlags Ptr DescriptorBindingFlags -> Int -> Ptr DescriptorBindingFlags
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorBindingFlags)))
    DescriptorSetLayoutBindingFlagsCreateInfo
-> IO DescriptorSetLayoutBindingFlagsCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DescriptorSetLayoutBindingFlagsCreateInfo
 -> IO DescriptorSetLayoutBindingFlagsCreateInfo)
-> DescriptorSetLayoutBindingFlagsCreateInfo
-> IO DescriptorSetLayoutBindingFlagsCreateInfo
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
           Vector DescriptorBindingFlags
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 count descriptor binding in the corresponding descriptor set
-- layout. If the variable count descriptor binding in the corresponding
-- descriptor set layout has a descriptor type of
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT'
-- then @pDescriptorCounts@[i] specifies the binding’s capacity in bytes.
-- If
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo'::@pSetLayouts@[i]
-- does not include a variable count descriptor binding, then
-- @pDescriptorCounts@[i] is ignored.
--
-- == Valid Usage
--
-- -   If @descriptorSetCount@ is not zero, @descriptorSetCount@ /must/
--     equal
--     'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo'::@descriptorSetCount@
--
-- -   If
--     'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo'::@pSetLayouts@[i]
--     has a variable descriptor count 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)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO'
--
-- -   If @descriptorSetCount@ is not @0@, @pDescriptorCounts@ /must/ be a
--     valid pointer to an array of @descriptorSetCount@ @uint32_t@ values
--
-- = See Also
--
-- '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
    -- descriptor count 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 :: DescriptorSetVariableDescriptorCountAllocateInfo
-> (Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b)
-> IO b
withCStruct x :: DescriptorSetVariableDescriptorCountAllocateInfo
x f :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b
f = Int
-> Int
-> (Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b)
 -> IO b)
-> (Ptr DescriptorSetVariableDescriptorCountAllocateInfo -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p -> Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> DescriptorSetVariableDescriptorCountAllocateInfo -> IO b -> IO b
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 :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> DescriptorSetVariableDescriptorCountAllocateInfo -> IO b -> IO b
pokeCStruct p :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p DescriptorSetVariableDescriptorCountAllocateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
descriptorCounts)) :: Word32))
    Ptr Word32
pPDescriptorCounts' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
descriptorCounts)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPDescriptorCounts' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
descriptorCounts)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32))) (Ptr Word32
pPDescriptorCounts')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> IO b -> IO b
pokeZeroCStruct p :: Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32
pPDescriptorCounts' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPDescriptorCounts' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountAllocateInfo
p Ptr DescriptorSetVariableDescriptorCountAllocateInfo
-> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32))) (Ptr Word32
pPDescriptorCounts')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

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


-- | VkDescriptorSetVariableDescriptorCountLayoutSupport - Structure
-- returning information about whether a descriptor set layout can be
-- supported
--
-- = Description
--
-- If the create info 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
-- create info 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 if the
-- @descriptorCount@ is one, 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
--
-- '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_EXT'
    -- 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
(DescriptorSetVariableDescriptorCountLayoutSupport
 -> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool)
-> (DescriptorSetVariableDescriptorCountLayoutSupport
    -> DescriptorSetVariableDescriptorCountLayoutSupport -> Bool)
-> Eq DescriptorSetVariableDescriptorCountLayoutSupport
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 :: DescriptorSetVariableDescriptorCountLayoutSupport
-> (Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b)
-> IO b
withCStruct x :: DescriptorSetVariableDescriptorCountLayoutSupport
x f :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b
f = Int
-> Int
-> (Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b)
 -> IO b)
-> (Ptr DescriptorSetVariableDescriptorCountLayoutSupport -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p -> Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport
-> IO b
-> IO b
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 :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> DescriptorSetVariableDescriptorCountLayoutSupport
-> IO b
-> IO b
pokeCStruct p :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p DescriptorSetVariableDescriptorCountLayoutSupport{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
maxVariableDescriptorCount)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> IO b -> IO b
pokeZeroCStruct p :: Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DescriptorSetVariableDescriptorCountLayoutSupport
p Ptr DescriptorSetVariableDescriptorCountLayoutSupport
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

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

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

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