Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- createDescriptorSetLayout :: forall a io. (Extendss DescriptorSetLayoutCreateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorSetLayoutCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io DescriptorSetLayout
- withDescriptorSetLayout :: forall a io r. (Extendss DescriptorSetLayoutCreateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorSetLayoutCreateInfo a -> Maybe AllocationCallbacks -> (io DescriptorSetLayout -> (DescriptorSetLayout -> io ()) -> r) -> r
- destroyDescriptorSetLayout :: forall io. MonadIO io => Device -> DescriptorSetLayout -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
- createDescriptorPool :: forall a io. (Extendss DescriptorPoolCreateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorPoolCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io DescriptorPool
- withDescriptorPool :: forall a io r. (Extendss DescriptorPoolCreateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorPoolCreateInfo a -> Maybe AllocationCallbacks -> (io DescriptorPool -> (DescriptorPool -> io ()) -> r) -> r
- destroyDescriptorPool :: forall io. MonadIO io => Device -> DescriptorPool -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
- resetDescriptorPool :: forall io. MonadIO io => Device -> DescriptorPool -> DescriptorPoolResetFlags -> io ()
- allocateDescriptorSets :: forall a io. (Extendss DescriptorSetAllocateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorSetAllocateInfo a -> io ("descriptorSets" ::: Vector DescriptorSet)
- withDescriptorSets :: forall a io r. (Extendss DescriptorSetAllocateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorSetAllocateInfo a -> (io (Vector DescriptorSet) -> (Vector DescriptorSet -> io ()) -> r) -> r
- freeDescriptorSets :: forall io. MonadIO io => Device -> DescriptorPool -> ("descriptorSets" ::: Vector DescriptorSet) -> io ()
- updateDescriptorSets :: forall io. MonadIO io => Device -> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)) -> ("descriptorCopies" ::: Vector CopyDescriptorSet) -> io ()
- data DescriptorBufferInfo = DescriptorBufferInfo {
- buffer :: Buffer
- offset :: DeviceSize
- range :: DeviceSize
- data DescriptorImageInfo = DescriptorImageInfo {}
- data WriteDescriptorSet (es :: [Type]) = WriteDescriptorSet {}
- data CopyDescriptorSet = CopyDescriptorSet {}
- data DescriptorSetLayoutBinding = DescriptorSetLayoutBinding {}
- data DescriptorSetLayoutCreateInfo (es :: [Type]) = DescriptorSetLayoutCreateInfo {}
- data DescriptorPoolSize = DescriptorPoolSize {}
- data DescriptorPoolCreateInfo (es :: [Type]) = DescriptorPoolCreateInfo {}
- data DescriptorSetAllocateInfo (es :: [Type]) = DescriptorSetAllocateInfo {}
- newtype DescriptorSet = DescriptorSet Word64
- newtype DescriptorSetLayout = DescriptorSetLayout Word64
- newtype DescriptorPool = DescriptorPool Word64
- newtype DescriptorPoolResetFlags = DescriptorPoolResetFlags Flags
- newtype DescriptorType where
- DescriptorType Int32
- pattern DESCRIPTOR_TYPE_SAMPLER :: DescriptorType
- pattern DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER :: DescriptorType
- pattern DESCRIPTOR_TYPE_SAMPLED_IMAGE :: DescriptorType
- pattern DESCRIPTOR_TYPE_STORAGE_IMAGE :: DescriptorType
- pattern DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER :: DescriptorType
- pattern DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER :: DescriptorType
- pattern DESCRIPTOR_TYPE_UNIFORM_BUFFER :: DescriptorType
- pattern DESCRIPTOR_TYPE_STORAGE_BUFFER :: DescriptorType
- pattern DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC :: DescriptorType
- pattern DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC :: DescriptorType
- pattern DESCRIPTOR_TYPE_INPUT_ATTACHMENT :: DescriptorType
- pattern DESCRIPTOR_TYPE_MUTABLE_EXT :: DescriptorType
- pattern DESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM :: DescriptorType
- pattern DESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM :: DescriptorType
- pattern DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV :: DescriptorType
- pattern DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR :: DescriptorType
- pattern DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK :: DescriptorType
- newtype DescriptorPoolCreateFlagBits where
- DescriptorPoolCreateFlagBits Flags
- pattern DESCRIPTOR_POOL_CREATE_FREE_DESCRIPTOR_SET_BIT :: DescriptorPoolCreateFlagBits
- pattern DESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_POOLS_BIT_NV :: DescriptorPoolCreateFlagBits
- pattern DESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_SETS_BIT_NV :: DescriptorPoolCreateFlagBits
- pattern DESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT :: DescriptorPoolCreateFlagBits
- pattern DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT :: DescriptorPoolCreateFlagBits
- type DescriptorPoolCreateFlags = DescriptorPoolCreateFlagBits
- newtype DescriptorSetLayoutCreateFlagBits where
- DescriptorSetLayoutCreateFlagBits Flags
- pattern DESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT :: DescriptorSetLayoutCreateFlagBits
- pattern DESCRIPTOR_SET_LAYOUT_CREATE_INDIRECT_BINDABLE_BIT_NV :: DescriptorSetLayoutCreateFlagBits
- pattern DESCRIPTOR_SET_LAYOUT_CREATE_EMBEDDED_IMMUTABLE_SAMPLERS_BIT_EXT :: DescriptorSetLayoutCreateFlagBits
- pattern DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT :: DescriptorSetLayoutCreateFlagBits
- pattern DESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR :: DescriptorSetLayoutCreateFlagBits
- pattern DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT :: DescriptorSetLayoutCreateFlagBits
- type DescriptorSetLayoutCreateFlags = DescriptorSetLayoutCreateFlagBits
Documentation
createDescriptorSetLayout Source #
:: forall a io. (Extendss DescriptorSetLayoutCreateInfo a, PokeChain a, MonadIO io) | |
=> Device |
|
-> DescriptorSetLayoutCreateInfo a |
|
-> ("allocator" ::: Maybe AllocationCallbacks) |
|
-> io DescriptorSetLayout |
vkCreateDescriptorSetLayout - Create a new descriptor set layout
Valid Usage (Implicit)
-
device
must be a validDevice
handle
-
pCreateInfo
must be a valid pointer to a validDescriptorSetLayoutCreateInfo
structure - If
pAllocator
is notNULL
,pAllocator
must be a valid pointer to a validAllocationCallbacks
structure -
pSetLayout
must be a valid pointer to aDescriptorSetLayout
handle
Return Codes
See Also
VK_VERSION_1_0,
AllocationCallbacks
,
DescriptorSetLayout
,
DescriptorSetLayoutCreateInfo
, Device
withDescriptorSetLayout :: forall a io r. (Extendss DescriptorSetLayoutCreateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorSetLayoutCreateInfo a -> Maybe AllocationCallbacks -> (io DescriptorSetLayout -> (DescriptorSetLayout -> io ()) -> r) -> r Source #
A convenience wrapper to make a compatible pair of calls to
createDescriptorSetLayout
and destroyDescriptorSetLayout
To ensure that destroyDescriptorSetLayout
is always called: pass
bracket
(or the allocate function from your
favourite resource management library) as the last argument.
To just extract the pair pass (,)
as the last argument.
destroyDescriptorSetLayout Source #
:: forall io. MonadIO io | |
=> Device |
|
-> DescriptorSetLayout |
|
-> ("allocator" ::: Maybe AllocationCallbacks) |
|
-> io () |
vkDestroyDescriptorSetLayout - Destroy a descriptor set layout object
Valid Usage
- If
AllocationCallbacks
were provided whendescriptorSetLayout
was created, a compatible set of callbacks must be provided here
- If no
AllocationCallbacks
were provided whendescriptorSetLayout
was created,pAllocator
must beNULL
Valid Usage (Implicit)
-
device
must be a validDevice
handle
- If
descriptorSetLayout
is notNULL_HANDLE
,descriptorSetLayout
must be a validDescriptorSetLayout
handle - If
pAllocator
is notNULL
,pAllocator
must be a valid pointer to a validAllocationCallbacks
structure - If
descriptorSetLayout
is a valid handle, it must have been created, allocated, or retrieved fromdevice
Host Synchronization
- Host access to
descriptorSetLayout
must be externally synchronized
See Also
VK_VERSION_1_0,
AllocationCallbacks
,
DescriptorSetLayout
,
Device
:: forall a io. (Extendss DescriptorPoolCreateInfo a, PokeChain a, MonadIO io) | |
=> Device |
|
-> DescriptorPoolCreateInfo a |
|
-> ("allocator" ::: Maybe AllocationCallbacks) |
|
-> io DescriptorPool |
vkCreateDescriptorPool - Creates a descriptor pool object
Description
The created descriptor pool is returned in pDescriptorPool
.
Valid Usage (Implicit)
-
device
must be a validDevice
handle
-
pCreateInfo
must be a valid pointer to a validDescriptorPoolCreateInfo
structure - If
pAllocator
is notNULL
,pAllocator
must be a valid pointer to a validAllocationCallbacks
structure -
pDescriptorPool
must be a valid pointer to aDescriptorPool
handle
Return Codes
See Also
VK_VERSION_1_0,
AllocationCallbacks
,
DescriptorPool
, DescriptorPoolCreateInfo
,
Device
withDescriptorPool :: forall a io r. (Extendss DescriptorPoolCreateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorPoolCreateInfo a -> Maybe AllocationCallbacks -> (io DescriptorPool -> (DescriptorPool -> io ()) -> r) -> r Source #
A convenience wrapper to make a compatible pair of calls to
createDescriptorPool
and destroyDescriptorPool
To ensure that destroyDescriptorPool
is always called: pass
bracket
(or the allocate function from your
favourite resource management library) as the last argument.
To just extract the pair pass (,)
as the last argument.
destroyDescriptorPool Source #
:: forall io. MonadIO io | |
=> Device |
|
-> DescriptorPool |
|
-> ("allocator" ::: Maybe AllocationCallbacks) |
|
-> io () |
vkDestroyDescriptorPool - Destroy a descriptor pool object
Description
When a pool is destroyed, all descriptor sets allocated from the pool are implicitly freed and become invalid. Descriptor sets allocated from a given pool do not need to be freed before destroying that descriptor pool.
Valid Usage
- All submitted
commands that refer to
descriptorPool
(via any allocated descriptor sets) must have completed execution
- If
AllocationCallbacks
were provided whendescriptorPool
was created, a compatible set of callbacks must be provided here - If no
AllocationCallbacks
were provided whendescriptorPool
was created,pAllocator
must beNULL
Valid Usage (Implicit)
-
device
must be a validDevice
handle
- If
descriptorPool
is notNULL_HANDLE
,descriptorPool
must be a validDescriptorPool
handle - If
pAllocator
is notNULL
,pAllocator
must be a valid pointer to a validAllocationCallbacks
structure - If
descriptorPool
is a valid handle, it must have been created, allocated, or retrieved fromdevice
Host Synchronization
- Host access to
descriptorPool
must be externally synchronized
See Also
:: forall io. MonadIO io | |
=> Device |
|
-> DescriptorPool |
|
-> DescriptorPoolResetFlags |
|
-> io () |
vkResetDescriptorPool - Resets a descriptor pool object
Description
Resetting a descriptor pool recycles all of the resources from all of the descriptor sets allocated from the descriptor pool back to the descriptor pool, and the descriptor sets are implicitly freed.
Valid Usage
Valid Usage (Implicit)
-
device
must be a validDevice
handle
-
descriptorPool
must be a validDescriptorPool
handle -
flags
must be0
-
descriptorPool
must have been created, allocated, or retrieved fromdevice
Host Synchronization
- Host access to
descriptorPool
must be externally synchronized
- Host access to any
DescriptorSet
objects allocated fromdescriptorPool
must be externally synchronized
Return Codes
See Also
VK_VERSION_1_0,
DescriptorPool
,
DescriptorPoolResetFlags
,
Device
allocateDescriptorSets Source #
:: forall a io. (Extendss DescriptorSetAllocateInfo a, PokeChain a, MonadIO io) | |
=> Device |
|
-> DescriptorSetAllocateInfo a |
|
-> io ("descriptorSets" ::: Vector DescriptorSet) |
vkAllocateDescriptorSets - Allocate one or more descriptor sets
Description
The allocated descriptor sets are returned in pDescriptorSets
.
When a descriptor set is allocated, the initial state is largely
uninitialized and all descriptors are undefined, with the exception that
samplers with a non-null pImmutableSamplers
are initialized on
allocation. Descriptors also become undefined if the underlying resource
or view object is destroyed. Descriptor sets containing undefined
descriptors can still be bound and used, subject to the following
conditions:
- For descriptor set bindings created with the
DESCRIPTOR_BINDING_PARTIALLY_BOUND_BIT
bit set, all descriptors in that binding that are dynamically used must have been populated before the descriptor set is consumed. - For descriptor set bindings created without the
DESCRIPTOR_BINDING_PARTIALLY_BOUND_BIT
bit set, all descriptors in that binding that are statically used must have been populated before the descriptor set is consumed. - Descriptor bindings with descriptor type of
DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
can be undefined when the descriptor set is consumed; though values in that block will be undefined. - Entries that are not used by a pipeline can have undefined descriptors.
If a call to allocateDescriptorSets
would cause the total number of
descriptor sets allocated from the pool to exceed the value of
DescriptorPoolCreateInfo
::maxSets
used to create
pAllocateInfo->descriptorPool
, then the allocation may fail due to
lack of space in the descriptor pool. Similarly, the allocation may
fail due to lack of space if the call to allocateDescriptorSets
would
cause the number of any given descriptor type to exceed the sum of all
the descriptorCount
members of each element of
DescriptorPoolCreateInfo
::pPoolSizes
with a type
equal to that
type.
Additionally, the allocation may also fail if a call to
allocateDescriptorSets
would cause the total number of inline uniform
block bindings allocated from the pool to exceed the value of
DescriptorPoolInlineUniformBlockCreateInfo
::maxInlineUniformBlockBindings
used to create the descriptor pool.
If the allocation fails due to no more space in the descriptor pool, and
not because of system or device memory exhaustion, then
ERROR_OUT_OF_POOL_MEMORY
must be
returned.
allocateDescriptorSets
can be used to create multiple descriptor
sets. If the creation of any of those descriptor sets fails, then the
implementation must destroy all successfully created descriptor set
objects from this command, set all entries of the pDescriptorSets
array to NULL_HANDLE
and return the error.
Valid Usage (Implicit)
-
device
must be a validDevice
handle
-
pAllocateInfo
must be a valid pointer to a validDescriptorSetAllocateInfo
structure -
pDescriptorSets
must be a valid pointer to an array ofpAllocateInfo->descriptorSetCount
DescriptorSet
handles -
pAllocateInfo->descriptorSetCount
must be greater than0
Host Synchronization
- Host access to
pAllocateInfo->descriptorPool
must be externally synchronized
Return Codes
See Also
VK_VERSION_1_0,
DescriptorSet
, DescriptorSetAllocateInfo
,
Device
withDescriptorSets :: forall a io r. (Extendss DescriptorSetAllocateInfo a, PokeChain a, MonadIO io) => Device -> DescriptorSetAllocateInfo a -> (io (Vector DescriptorSet) -> (Vector DescriptorSet -> io ()) -> r) -> r Source #
A convenience wrapper to make a compatible pair of calls to
allocateDescriptorSets
and freeDescriptorSets
To ensure that freeDescriptorSets
is always called: pass
bracket
(or the allocate function from your
favourite resource management library) as the last argument.
To just extract the pair pass (,)
as the last argument.
:: forall io. MonadIO io | |
=> Device |
|
-> DescriptorPool |
|
-> ("descriptorSets" ::: Vector DescriptorSet) |
|
-> io () |
vkFreeDescriptorSets - Free one or more descriptor sets
Description
After calling freeDescriptorSets
, all descriptor sets in
pDescriptorSets
are invalid.
Valid Usage
-
pDescriptorSets
must be a valid pointer to an array ofdescriptorSetCount
DescriptorSet
handles, each element of which must either be a valid handle orNULL_HANDLE
-
descriptorPool
must have been created with theDESCRIPTOR_POOL_CREATE_FREE_DESCRIPTOR_SET_BIT
flag
Valid Usage (Implicit)
-
device
must be a validDevice
handle
-
descriptorPool
must be a validDescriptorPool
handle -
descriptorSetCount
must be greater than0
-
descriptorPool
must have been created, allocated, or retrieved fromdevice
- Each element of
pDescriptorSets
that is a valid handle must have been created, allocated, or retrieved fromdescriptorPool
Host Synchronization
- Host access to
descriptorPool
must be externally synchronized
- Host access to each member of
pDescriptorSets
must be externally synchronized
Return Codes
See Also
:: forall io. MonadIO io | |
=> Device |
|
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)) |
|
-> ("descriptorCopies" ::: Vector CopyDescriptorSet) |
|
-> io () |
vkUpdateDescriptorSets - Update the contents of a descriptor set object
Description
The operations described by pDescriptorWrites
are performed first,
followed by the operations described by pDescriptorCopies
. Within each
array, the operations are performed in the order they appear in the
array.
Each element in the pDescriptorWrites
array describes an operation
updating the descriptor set using descriptors for resources specified in
the structure.
Each element in the pDescriptorCopies
array is a CopyDescriptorSet
structure describing an operation copying descriptors between sets.
If the dstSet
member of any element of pDescriptorWrites
or
pDescriptorCopies
is bound, accessed, or modified by any command that
was recorded to a command buffer which is currently in the
recording or executable state,
and any of the descriptor bindings that are updated were not created
with the
DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT
or
DESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT
bits set, that command buffer becomes
invalid.
Valid Usage
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
orDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
, elements of thepTexelBufferView
member ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_UNIFORM_BUFFER
,DESCRIPTOR_TYPE_STORAGE_BUFFER
,DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
, orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
, thebuffer
member of any element of thepBufferInfo
member ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_SAMPLER
orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, anddstSet
was not allocated with a layout that included immutable samplers fordstBinding
withdescriptorType
, thesampler
member of any element of thepImageInfo
member ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_SAMPLED_IMAGE
,DESCRIPTOR_TYPE_STORAGE_IMAGE
,DESCRIPTOR_TYPE_INPUT_ATTACHMENT
, orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
theimageView
member of any element ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR
, elements of thepAccelerationStructures
member of aWriteDescriptorSetAccelerationStructureKHR
structure in thepNext
chain ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV
, elements of thepAccelerationStructures
member of aWriteDescriptorSetAccelerationStructureNV
structure in thepNext
chain ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM
orDESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM
, theimageView
member of any element ofpDescriptorWrites
[i] must have been created ondevice
- For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_SAMPLER
,DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
,DESCRIPTOR_TYPE_SAMPLED_IMAGE
,DESCRIPTOR_TYPE_STORAGE_IMAGE
, orDESCRIPTOR_TYPE_INPUT_ATTACHMENT
,pDescriptorWrites
[i].pImageInfo
must be a valid pointer to an array ofpDescriptorWrites
[i].descriptorCount
validDescriptorImageInfo
structures - For each
element i where
pDescriptorWrites
[i].descriptorType
isDESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM
orDESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM
,pDescriptorWrites
[i].pImageInfo
must be a valid pointer to an array ofpDescriptorWrites
[i].descriptorCount
validDescriptorImageInfo
structures - The
dstSet
member of each element ofpDescriptorWrites
orpDescriptorCopies
for bindings which were created without theDESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT
orDESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT
bits set must not be used by any command that was recorded to a command buffer which is in the pending state - Host access to
pDescriptorWrites
[i].dstSet
andpDescriptorCopies
[i].dstSet
must be externally synchronized unless explicitly denoted otherwise for specific flags
Valid Usage (Implicit)
-
device
must be a validDevice
handle
- If
descriptorWriteCount
is not0
,pDescriptorWrites
must be a valid pointer to an array ofdescriptorWriteCount
validWriteDescriptorSet
structures - If
descriptorCopyCount
is not0
,pDescriptorCopies
must be a valid pointer to an array ofdescriptorCopyCount
validCopyDescriptorSet
structures
See Also
VK_VERSION_1_0,
CopyDescriptorSet
, Device
,
WriteDescriptorSet
data DescriptorBufferInfo Source #
VkDescriptorBufferInfo - Structure specifying descriptor buffer information
Description
For
DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
and
DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
descriptor types, offset
is the base offset from which the dynamic
offset is applied and range
is the static size used for all dynamic
offsets.
When range
is WHOLE_SIZE
the effective
range is calculated at updateDescriptorSets
is by taking the size of
buffer
minus the offset
.
Valid Usage
- If
range
is not equal toWHOLE_SIZE
,range
must be greater than0
- If
range
is not equal toWHOLE_SIZE
,range
must be less than or equal to the size ofbuffer
minusoffset
- If the
nullDescriptor
feature is not enabled,
buffer
must not beNULL_HANDLE
- If
buffer
isNULL_HANDLE
,offset
must be zero andrange
must beWHOLE_SIZE
Valid Usage (Implicit)
- If
buffer
is notNULL_HANDLE
,buffer
must be a validBuffer
handle
See Also
DescriptorBufferInfo | |
|
Instances
data DescriptorImageInfo Source #
VkDescriptorImageInfo - Structure specifying descriptor image information
Description
Members of DescriptorImageInfo
that are not used in an update (as
described above) are ignored.
Valid Usage
- If
imageView
is a 2D view created from a 3D image, thendescriptorType
must beDESCRIPTOR_TYPE_STORAGE_IMAGE
,DESCRIPTOR_TYPE_SAMPLED_IMAGE
, orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
- If
imageView
is a 2D view created from a 3D image, then the image must have been created withIMAGE_CREATE_2D_VIEW_COMPATIBLE_BIT_EXT
set - If the
image2DViewOf3D
feature is not enabled or
descriptorType
is notDESCRIPTOR_TYPE_STORAGE_IMAGE
thenimageView
must not be a 2D view created from a 3D image - If the
sampler2DViewOf3D
feature is not enabled or
descriptorType
is notDESCRIPTOR_TYPE_SAMPLED_IMAGE
orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
thenimageView
must not be a 2D view created from a 3D image - If
imageView
is created from a depth/stencil image, theaspectMask
used to create theimageView
must include eitherIMAGE_ASPECT_DEPTH_BIT
orIMAGE_ASPECT_STENCIL_BIT
but not both -
imageLayout
must match the actualImageLayout
of each subresource accessible fromimageView
at the time this descriptor is accessed as defined by the image layout matching rules - If
sampler
is used and theFormat
of the image is a multi-planar format, the image must have been created withIMAGE_CREATE_MUTABLE_FORMAT_BIT
, and theaspectMask
of theimageView
must be a valid multi-planar aspect mask bit - If the
VK_KHR_portability_subset
extension is enabled, andPhysicalDevicePortabilitySubsetFeaturesKHR
::mutableComparisonSamplers
isFALSE
, thensampler
must have been created withSamplerCreateInfo
::compareEnable
set toFALSE
Valid Usage (Implicit)
- Both of
imageView
, andsampler
that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the sameDevice
See Also
VK_VERSION_1_0,
DescriptorDataEXT
,
ImageLayout
,
ImageView
, Sampler
,
WriteDescriptorSet
DescriptorImageInfo | |
|
Instances
data WriteDescriptorSet (es :: [Type]) Source #
VkWriteDescriptorSet - Structure specifying the parameters of a descriptor set write operation
Description
Only one of pImageInfo
, pBufferInfo
, or pTexelBufferView
members
is used according to the descriptor type specified in the
descriptorType
member of the containing WriteDescriptorSet
structure, or none of them in case descriptorType
is
DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
,
in which case the source data for the descriptor writes is taken from
the
WriteDescriptorSetInlineUniformBlock
structure included in the pNext
chain of WriteDescriptorSet
, or if
descriptorType
is
DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR
,
in which case the source data for the descriptor writes is taken from
the
WriteDescriptorSetAccelerationStructureKHR
structure in the pNext
chain of WriteDescriptorSet
, or if
descriptorType
is
DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV
,
in which case the source data for the descriptor writes is taken from
the
WriteDescriptorSetAccelerationStructureNV
structure in the pNext
chain of WriteDescriptorSet
, as specified
below.
If the
nullDescriptor
feature is enabled, the buffer, acceleration structure, imageView, or
bufferView can be NULL_HANDLE
. Loads from
a null descriptor return zero values and stores and atomics to a null
descriptor are discarded. A null acceleration structure descriptor
results in the miss shader being invoked.
If the destination descriptor is a mutable descriptor, the active
descriptor type for the destination descriptor becomes descriptorType
.
If the dstBinding
has fewer than descriptorCount
array elements
remaining starting from dstArrayElement
, then the remainder will be
used to update the subsequent binding - dstBinding
+1 starting at array
element zero. If a binding has a descriptorCount
of zero, it is
skipped. This behavior applies recursively, with the update affecting
consecutive bindings as needed to update all descriptorCount
descriptors. Consecutive bindings must have identical
DescriptorType
,
ShaderStageFlags
,
DescriptorBindingFlagBits
,
and immutable samplers references. In addition, if the
DescriptorType
is
DESCRIPTOR_TYPE_MUTABLE_EXT
, the
supported descriptor types in
MutableDescriptorTypeCreateInfoEXT
must be equally defined.
Note
The same behavior applies to bindings with a descriptor type of
DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
where descriptorCount
specifies the number of bytes to update while
dstArrayElement
specifies the starting byte offset, thus in this case
if the dstBinding
has a smaller byte size than the sum of
dstArrayElement
and descriptorCount
, then the remainder will be used
to update the subsequent binding - dstBinding
+1 starting at offset
zero. This falls out as a special case of the above rule.
Valid Usage
-
dstBinding
must be less than or equal to the maximum value ofbinding
of allDescriptorSetLayoutBinding
structures specified whendstSet
’s descriptor set layout was created
-
dstBinding
must be a binding with a non-zerodescriptorCount
- All consecutive
bindings updated via a single
WriteDescriptorSet
structure, except those with adescriptorCount
of zero, must have identicaldescriptorType
andstageFlags
- All consecutive
bindings updated via a single
WriteDescriptorSet
structure, except those with adescriptorCount
of zero, must all either use immutable samplers or must all not use immutable samplers -
descriptorType
must match the type ofdstBinding
withindstSet
-
dstSet
must be a validDescriptorSet
handle - The sum of
dstArrayElement
anddescriptorCount
must be less than or equal to the number of array elements in the descriptor set binding specified bydstBinding
, and all applicable consecutive bindings, as described by https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptorsets-updates-consecutive - If
descriptorType
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
,dstArrayElement
must be an integer multiple of4
- If
descriptorType
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
,descriptorCount
must be an integer multiple of4
- If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
orDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
, each element ofpTexelBufferView
must be either a validBufferView
handle orNULL_HANDLE
- If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
orDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
and the nullDescriptor feature is not enabled, each element ofpTexelBufferView
must not beNULL_HANDLE
- If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_BUFFER
,DESCRIPTOR_TYPE_STORAGE_BUFFER
,DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
, orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
,pBufferInfo
must be a valid pointer to an array ofdescriptorCount
validDescriptorBufferInfo
structures - If
descriptorType
isDESCRIPTOR_TYPE_SAMPLER
orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, anddstSet
was not allocated with a layout that included immutable samplers fordstBinding
withdescriptorType
, thesampler
member of each element ofpImageInfo
must be a validSampler
object - If
descriptorType
isDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
,DESCRIPTOR_TYPE_SAMPLED_IMAGE
, orDESCRIPTOR_TYPE_STORAGE_IMAGE
, theimageView
member of each element ofpImageInfo
must be either a validImageView
handle orNULL_HANDLE
- If
descriptorType
isDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
,DESCRIPTOR_TYPE_SAMPLED_IMAGE
, orDESCRIPTOR_TYPE_STORAGE_IMAGE
, and the nullDescriptor feature is not enabled, theimageView
member of each element ofpImageInfo
must not beNULL_HANDLE
- If
descriptorType
isDESCRIPTOR_TYPE_INPUT_ATTACHMENT
, theimageView
member of each element ofpImageInfo
must not beNULL_HANDLE
- If
descriptorType
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
, thepNext
chain must include aWriteDescriptorSetInlineUniformBlock
structure whosedataSize
member equalsdescriptorCount
- If
descriptorType
isDESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR
, thepNext
chain must include aWriteDescriptorSetAccelerationStructureKHR
structure whoseaccelerationStructureCount
member equalsdescriptorCount
- If
descriptorType
isDESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV
, thepNext
chain must include aWriteDescriptorSetAccelerationStructureNV
structure whoseaccelerationStructureCount
member equalsdescriptorCount
- If
descriptorType
isDESCRIPTOR_TYPE_SAMPLED_IMAGE
, then theimageView
member of eachpImageInfo
element must have been created without aSamplerYcbcrConversionInfo
structure in itspNext
chain - If
descriptorType
isDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, and if any element ofpImageInfo
has aimageView
member that was created with aSamplerYcbcrConversionInfo
structure in itspNext
chain, thendstSet
must have been allocated with a layout that included immutable samplers fordstBinding
, and the corresponding immutable sampler must have been created with an identically definedSamplerYcbcrConversionInfo
object - If
descriptorType
isDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, anddstSet
was allocated with a layout that included immutable samplers fordstBinding
, then theimageView
member of each element ofpImageInfo
which corresponds to an immutable sampler that enables sampler Y′CBCR conversion must have been created with aSamplerYcbcrConversionInfo
structure in itspNext
chain with an identically definedSamplerYcbcrConversionInfo
to the corresponding immutable sampler - If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_BUFFER
orDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
, theoffset
member of each element ofpBufferInfo
must be a multiple ofPhysicalDeviceLimits
::minUniformBufferOffsetAlignment
- If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_BUFFER
orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
, theoffset
member of each element ofpBufferInfo
must be a multiple ofPhysicalDeviceLimits
::minStorageBufferOffsetAlignment
- If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_BUFFER
,DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
,DESCRIPTOR_TYPE_STORAGE_BUFFER
, orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
, and thebuffer
member of any element ofpBufferInfo
is the handle of a non-sparse buffer, then that buffer must be bound completely and contiguously to a singleDeviceMemory
object - If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_BUFFER
orDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
, thebuffer
member of each element ofpBufferInfo
must have been created withBUFFER_USAGE_UNIFORM_BUFFER_BIT
set - If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_BUFFER
orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
, thebuffer
member of each element ofpBufferInfo
must have been created withBUFFER_USAGE_STORAGE_BUFFER_BIT
set - If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_BUFFER
orDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
, therange
member of each element ofpBufferInfo
, or the effective range ifrange
isWHOLE_SIZE
, must be less than or equal toPhysicalDeviceLimits
::maxUniformBufferRange
- If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_BUFFER
orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
, therange
member of each element ofpBufferInfo
, or the effective range ifrange
isWHOLE_SIZE
, must be less than or equal toPhysicalDeviceLimits
::maxStorageBufferRange
- If
descriptorType
isDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
, thepTexelBufferView
buffer view usage must includeBUFFER_USAGE_UNIFORM_TEXEL_BUFFER_BIT
- If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
, thepTexelBufferView
buffer view usage must includeBUFFER_USAGE_STORAGE_TEXEL_BUFFER_BIT
- If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_IMAGE
orDESCRIPTOR_TYPE_INPUT_ATTACHMENT
, theimageView
member of each element ofpImageInfo
must have been created with the identity swizzle - If
descriptorType
isDESCRIPTOR_TYPE_SAMPLED_IMAGE
orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, theimageView
member of each element ofpImageInfo
must have been created withIMAGE_USAGE_SAMPLED_BIT
set - If
descriptorType
isDESCRIPTOR_TYPE_SAMPLED_IMAGE
theimageLayout
member of each element ofpImageInfo
must be a member of the list given in Sampled Image - If
descriptorType
isDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
theimageLayout
member of each element ofpImageInfo
must be a member of the list given in Combined Image Sampler - If
descriptorType
isDESCRIPTOR_TYPE_INPUT_ATTACHMENT
theimageLayout
member of each element ofpImageInfo
must be a member of the list given in Input Attachment - If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_IMAGE
theimageLayout
member of each element ofpImageInfo
must be a member of the list given in Storage Image - If
descriptorType
isDESCRIPTOR_TYPE_INPUT_ATTACHMENT
, theimageView
member of each element ofpImageInfo
must have been created withIMAGE_USAGE_INPUT_ATTACHMENT_BIT
set - If
descriptorType
isDESCRIPTOR_TYPE_STORAGE_IMAGE
, theimageView
member of each element ofpImageInfo
must have been created withIMAGE_USAGE_STORAGE_BIT
set - If
descriptorType
isDESCRIPTOR_TYPE_SAMPLER
, thendstSet
must not have been allocated with a layout that included immutable samplers fordstBinding
- If the
DescriptorSetLayoutBinding
fordstSet
atdstBinding
isDESCRIPTOR_TYPE_MUTABLE_EXT
, the new active descriptor typedescriptorType
must exist in the correspondingpMutableDescriptorTypeLists
list fordstBinding
- If
descriptorType
isDESCRIPTOR_TYPE_INPUT_ATTACHMENT
, theimageView
member of each element ofpImageInfo
must have either been created without aImageViewMinLodCreateInfoEXT
included in thepNext
chain or with aImageViewMinLodCreateInfoEXT
::minLod
of0.0
- If
descriptorType
isDESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM
, theimageView
member of each element ofpImageInfo
must have been created with a view created with animage
created withIMAGE_USAGE_SAMPLE_WEIGHT_BIT_QCOM
- If
descriptorType
isDESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM
, theimageView
member of each element ofpImageInfo
must have been created with a view created with animage
created withIMAGE_USAGE_SAMPLE_BLOCK_MATCH_BIT_QCOM
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_WRITE_DESCRIPTOR_SET
- Each
pNext
member of any structure (including this one) in thepNext
chain must be eitherNULL
or a pointer to a valid instance ofWriteDescriptorSetAccelerationStructureKHR
,WriteDescriptorSetAccelerationStructureNV
, orWriteDescriptorSetInlineUniformBlock
- The
sType
value of each struct in thepNext
chain must be unique -
descriptorType
must be a validDescriptorType
value -
descriptorCount
must be greater than0
- Both of
dstSet
, and the elements ofpTexelBufferView
that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the sameDevice
See Also
VK_VERSION_1_0,
BufferView
, DescriptorBufferInfo
,
DescriptorImageInfo
, DescriptorSet
,
DescriptorType
,
StructureType
,
cmdPushDescriptorSetKHR
,
updateDescriptorSets
WriteDescriptorSet | |
|
Instances
data CopyDescriptorSet Source #
VkCopyDescriptorSet - Structure specifying a copy descriptor set operation
Description
If the DescriptorSetLayoutBinding
for dstBinding
is
DESCRIPTOR_TYPE_MUTABLE_EXT
and
srcBinding
is not
DESCRIPTOR_TYPE_MUTABLE_EXT
, the
new active descriptor type becomes the descriptor type of srcBinding
.
If both DescriptorSetLayoutBinding
for srcBinding
and dstBinding
are DESCRIPTOR_TYPE_MUTABLE_EXT
,
the active descriptor type in each source descriptor is copied into the
corresponding destination descriptor. The active descriptor type can
be different for each source descriptor.
Note
The intention is that copies to and from mutable descriptors is a simple
memcpy. Copies between non-mutable and mutable descriptors are expected
to require one memcpy per descriptor to handle the difference in size,
but this use case with more than one descriptorCount
is considered
rare.
Valid Usage
- The sum of
srcArrayElement
anddescriptorCount
must be less than or equal to the number of array elements in the descriptor set binding specified bysrcBinding
, and all applicable consecutive bindings, as described by https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptorsets-updates-consecutive -
dstBinding
must be a valid binding withindstSet
- The sum of
dstArrayElement
anddescriptorCount
must be less than or equal to the number of array elements in the descriptor set binding specified bydstBinding
, and all applicable consecutive bindings, as described by https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptorsets-updates-consecutive - The type of
dstBinding
withindstSet
must be equal to the type ofsrcBinding
withinsrcSet
- If
srcSet
is equal todstSet
, then the source and destination ranges of descriptors must not overlap, where the ranges may include array elements from consecutive bindings as described by https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptorsets-updates-consecutive - If the descriptor type
of the descriptor set binding specified by
srcBinding
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
,srcArrayElement
must be an integer multiple of4
- If the descriptor type
of the descriptor set binding specified by
dstBinding
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
,dstArrayElement
must be an integer multiple of4
- If the descriptor type
of the descriptor set binding specified by either
srcBinding
ordstBinding
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
,descriptorCount
must be an integer multiple of4
- If
srcSet
’s layout was created with theDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
flag set, thendstSet
’s layout must also have been created with theDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
flag set - If
srcSet
’s layout was created without either theDESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT
flag or theDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
flag set, thendstSet
’s layout must have been created without theDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
flag set - If the descriptor pool from
which
srcSet
was allocated was created with theDESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
flag set, then the descriptor pool from whichdstSet
was allocated must also have been created with theDESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
flag set - If the descriptor pool from
which
srcSet
was allocated was created without either theDESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT
flag or theDESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
flag set, then the descriptor pool from whichdstSet
was allocated must have been created without theDESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
flag set - If the descriptor type
of the descriptor set binding specified by
dstBinding
isDESCRIPTOR_TYPE_SAMPLER
, thendstSet
must not have been allocated with a layout that included immutable samplers fordstBinding
- If
DescriptorSetLayoutBinding
fordstSet
atdstBinding
isDESCRIPTOR_TYPE_MUTABLE_EXT
, the new active descriptor type must exist in the correspondingpMutableDescriptorTypeLists
list fordstBinding
if the new active descriptor type is notDESCRIPTOR_TYPE_MUTABLE_EXT
- If
DescriptorSetLayoutBinding
forsrcSet
atsrcBinding
isDESCRIPTOR_TYPE_MUTABLE_EXT
and theDescriptorSetLayoutBinding
fordstSet
atdstBinding
is notDESCRIPTOR_TYPE_MUTABLE_EXT
, the active descriptor type for the source descriptor must match the descriptor type ofdstBinding
- If
DescriptorSetLayoutBinding
fordstSet
atdstBinding
isDESCRIPTOR_TYPE_MUTABLE_EXT
, and the new active descriptor type isDESCRIPTOR_TYPE_MUTABLE_EXT
, thepMutableDescriptorTypeLists
forsrcBinding
anddstBinding
must match exactly
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_COPY_DESCRIPTOR_SET
-
pNext
must beNULL
-
srcSet
must be a validDescriptorSet
handle -
dstSet
must be a validDescriptorSet
handle - Both of
dstSet
, andsrcSet
must have been created, allocated, or retrieved from the sameDevice
See Also
VK_VERSION_1_0,
DescriptorSet
,
StructureType
,
updateDescriptorSets
CopyDescriptorSet | |
|
Instances
data DescriptorSetLayoutBinding Source #
VkDescriptorSetLayoutBinding - Structure specifying a descriptor set layout binding
Description
The above layout definition allows the descriptor bindings to be
specified sparsely such that not all binding numbers between 0 and the
maximum binding number need to be specified in the pBindings
array.
Bindings that are not specified have a descriptorCount
and
stageFlags
of zero, and the value of descriptorType
is undefined.
However, all binding numbers between 0 and the maximum binding number in
the DescriptorSetLayoutCreateInfo
::pBindings
array may consume
memory in the descriptor set layout even if not all descriptor bindings
are used, though it should not consume additional memory from the
descriptor pool.
Note
The maximum binding number specified should be as compact as possible to avoid wasted memory.
Valid Usage
- If
descriptorType
isDESCRIPTOR_TYPE_SAMPLER
orDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, anddescriptorCount
is not0
andpImmutableSamplers
is notNULL
,pImmutableSamplers
must be a valid pointer to an array ofdescriptorCount
validSampler
handles
- If the
inlineUniformBlock
feature is not enabled,
descriptorType
must not beDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
- If
descriptorType
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
thendescriptorCount
must be a multiple of4
- If
descriptorType
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
andDescriptorSetLayoutCreateInfo
::flags
does not containDESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT
thendescriptorCount
must be less than or equal toPhysicalDeviceInlineUniformBlockProperties
::maxInlineUniformBlockSize
- If
DescriptorSetLayoutCreateInfo
::flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_EMBEDDED_IMMUTABLE_SAMPLERS_BIT_EXT
,descriptorType
must beDESCRIPTOR_TYPE_SAMPLER
- If
DescriptorSetLayoutCreateInfo
::flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_EMBEDDED_IMMUTABLE_SAMPLERS_BIT_EXT
,descriptorCount
must less than or equal to1
- If
DescriptorSetLayoutCreateInfo
::flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_EMBEDDED_IMMUTABLE_SAMPLERS_BIT_EXT
, anddescriptorCount
is equal to1
,pImmutableSamplers
must not beNULL
- If
descriptorCount
is not0
,stageFlags
must be a valid combination ofShaderStageFlagBits
values - If
descriptorType
isDESCRIPTOR_TYPE_INPUT_ATTACHMENT
anddescriptorCount
is not0
, thenstageFlags
must be0
orSHADER_STAGE_FRAGMENT_BIT
- The
sampler objects indicated by
pImmutableSamplers
must not have aborderColor
with one of the valuesBORDER_COLOR_FLOAT_CUSTOM_EXT
orBORDER_COLOR_INT_CUSTOM_EXT
- If
descriptorType
isDESCRIPTOR_TYPE_MUTABLE_EXT
, thenpImmutableSamplers
must beNULL
Valid Usage (Implicit)
-
descriptorType
must be a validDescriptorType
value
See Also
VK_VERSION_1_0,
DescriptorSetLayoutCreateInfo
,
DescriptorType
,
Sampler
,
ShaderStageFlags
DescriptorSetLayoutBinding | |
|
Instances
Show DescriptorSetLayoutBinding Source # | |
Defined in Vulkan.Core10.DescriptorSet showsPrec :: Int -> DescriptorSetLayoutBinding -> ShowS # show :: DescriptorSetLayoutBinding -> String # showList :: [DescriptorSetLayoutBinding] -> ShowS # | |
FromCStruct DescriptorSetLayoutBinding Source # | |
ToCStruct DescriptorSetLayoutBinding Source # | |
Defined in Vulkan.Core10.DescriptorSet withCStruct :: DescriptorSetLayoutBinding -> (Ptr DescriptorSetLayoutBinding -> IO b) -> IO b Source # pokeCStruct :: Ptr DescriptorSetLayoutBinding -> DescriptorSetLayoutBinding -> IO b -> IO b Source # withZeroCStruct :: (Ptr DescriptorSetLayoutBinding -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr DescriptorSetLayoutBinding -> IO b -> IO b Source # cStructSize :: Int Source # | |
Zero DescriptorSetLayoutBinding Source # | |
Defined in Vulkan.Core10.DescriptorSet |
data DescriptorSetLayoutCreateInfo (es :: [Type]) Source #
VkDescriptorSetLayoutCreateInfo - Structure specifying parameters of a newly created descriptor set layout
Valid Usage
- The
DescriptorSetLayoutBinding
::binding
members of the elements of thepBindings
array must each have different values
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR
, then all elements ofpBindings
must not have adescriptorType
ofDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR
, then all elements ofpBindings
must not have adescriptorType
ofDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR
, then the total number of elements of all bindings must be less than or equal toPhysicalDevicePushDescriptorPropertiesKHR
::maxPushDescriptors
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR
,flags
must not containDESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR
,pBindings
must not have adescriptorType
ofDESCRIPTOR_TYPE_MUTABLE_EXT
- If any binding
has the
DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT
bit set,flags
must includeDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
- If any
binding has the
DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT
bit set, then all bindings must not havedescriptorType
ofDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
,flags
must not containDESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT
- If any
element
pBindings
[i] has adescriptorType
ofDESCRIPTOR_TYPE_MUTABLE_EXT
, then aMutableDescriptorTypeCreateInfoEXT
must be present in thepNext
chain, andmutableDescriptorTypeListCount
must be greater than i - If a
binding has a
descriptorType
value ofDESCRIPTOR_TYPE_MUTABLE_EXT
, thenpImmutableSamplers
must beNULL
-
If
PhysicalDeviceMutableDescriptorTypeFeaturesEXT
::mutableDescriptorType
is not enabled,pBindings
must not contain adescriptorType
ofDESCRIPTOR_TYPE_MUTABLE_EXT
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT
,PhysicalDeviceMutableDescriptorTypeFeaturesEXT
::mutableDescriptorType
must be enabled - If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT
, then all elements ofpBindings
must not have adescriptorType
ofDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_EMBEDDED_IMMUTABLE_SAMPLERS_BIT_EXT
,flags
must also containDESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT
, thenflags
must not containDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
- If
flags
containsDESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT
, thenflags
must not containDESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_VALVE
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_CREATE_INFO
- Each
pNext
member of any structure (including this one) in thepNext
chain must be eitherNULL
or a pointer to a valid instance ofDescriptorSetLayoutBindingFlagsCreateInfo
orMutableDescriptorTypeCreateInfoEXT
- The
sType
value of each struct in thepNext
chain must be unique -
flags
must be a valid combination ofDescriptorSetLayoutCreateFlagBits
values - If
bindingCount
is not0
,pBindings
must be a valid pointer to an array ofbindingCount
validDescriptorSetLayoutBinding
structures
See Also
VK_VERSION_1_0,
DescriptorSetLayoutBinding
,
DescriptorSetLayoutCreateFlags
,
StructureType
,
createDescriptorSetLayout
,
getDescriptorSetLayoutSupport
,
getDescriptorSetLayoutSupportKHR
DescriptorSetLayoutCreateInfo | |
|
Instances
data DescriptorPoolSize Source #
VkDescriptorPoolSize - Structure specifying descriptor pool size
Description
Note
When creating a descriptor pool that will contain descriptors for
combined image samplers of multi-planar formats, an application needs to
account for non-trivial descriptor consumption when choosing the
descriptorCount
value, as indicated by
SamplerYcbcrConversionImageFormatProperties
::combinedImageSamplerDescriptorCount
.
Valid Usage
- If
type
isDESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
thendescriptorCount
must be a multiple of4
Valid Usage (Implicit)
-
type
must be a validDescriptorType
value
See Also
DescriptorPoolSize | |
|
Instances
data DescriptorPoolCreateInfo (es :: [Type]) Source #
VkDescriptorPoolCreateInfo - Structure specifying parameters of a newly created descriptor pool
Description
If multiple DescriptorPoolSize
structures containing the same
descriptor type appear in the pPoolSizes
array then the pool will be
created with enough storage for the total number of descriptors of each
type.
Fragmentation of a descriptor pool is possible and may lead to descriptor set allocation failures. A failure due to fragmentation is defined as failing a descriptor set allocation despite the sum of all outstanding descriptor set allocations from the pool plus the requested allocation requiring no more than the total number of descriptors requested at pool creation. Implementations provide certain guarantees of when fragmentation must not cause allocation failure, as described below.
If a descriptor pool has not had any descriptor sets freed since it was
created or most recently reset then fragmentation must not cause an
allocation failure (note that this is always the case for a pool created
without the
DESCRIPTOR_POOL_CREATE_FREE_DESCRIPTOR_SET_BIT
bit set). Additionally, if all sets allocated from the pool since it was
created or most recently reset use the same number of descriptors (of
each type) and the requested allocation also uses that same number of
descriptors (of each type), then fragmentation must not cause an
allocation failure.
If an allocation failure occurs due to fragmentation, an application can create an additional descriptor pool to perform further descriptor set allocations.
If flags
has the
DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
bit set, descriptor pool creation may fail with the error
ERROR_FRAGMENTATION
if the total number of
descriptors across all pools (including this one) created with this bit
set exceeds maxUpdateAfterBindDescriptorsInAllPools
, or if
fragmentation of the underlying hardware resources occurs.
If a pPoolSizes
[i]::type
is
DESCRIPTOR_TYPE_MUTABLE_EXT
, a
MutableDescriptorTypeCreateInfoEXT
struct in the pNext
chain can be used to specify which mutable
descriptor types can be allocated from the pool. If included in the
pNext
chain,
MutableDescriptorTypeCreateInfoEXT
::pMutableDescriptorTypeLists
[i]
specifies which kind of
DESCRIPTOR_TYPE_MUTABLE_EXT
descriptors can be allocated from this pool entry. If
MutableDescriptorTypeCreateInfoEXT
does not exist in the pNext
chain, or
MutableDescriptorTypeCreateInfoEXT
::pMutableDescriptorTypeLists
[i]
is out of range, the descriptor pool allocates enough memory to be able
to allocate a
DESCRIPTOR_TYPE_MUTABLE_EXT
descriptor with any supported
DescriptorType
as a mutable
descriptor. A mutable descriptor can be allocated from a pool entry if
the type list in DescriptorSetLayoutCreateInfo
is a subset of the type
list declared in the descriptor pool, or if the pool entry is created
without a descriptor type list. Multiple pPoolSizes
entries with
DESCRIPTOR_TYPE_MUTABLE_EXT
can
be declared. When multiple such pool entries are present in
pPoolSizes
, they specify sets of supported descriptor types which
either fully overlap, partially overlap, or are disjoint. Two sets fully
overlap if the sets of supported descriptor types are equal. If the sets
are not disjoint they partially overlap. A pool entry without a
MutableDescriptorTypeListEXT
assigned to it is considered to partially overlap any other pool entry
which has a
MutableDescriptorTypeListEXT
assigned to it. The application must ensure that partial overlap does
not exist in pPoolSizes
.
Note
The requirement of no partial overlap is intended to resolve ambiguity
for validation as there is no confusion which pPoolSizes
entries will
be allocated from. An implementation is not expected to depend on this
requirement.
Valid Usage
-
If the
descriptorPoolOverallocation
feature is not enabled, or
flags
does not haveDESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_SETS_BIT_NV
set,maxSets
must be greater than0
- If
flags
has theDESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_SETS_BIT_NV
orDESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_POOLS_BIT_NV
bits set, then descriptorPoolOverallocation must be enabled - If
flags
has theDESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT
bit set, then theDESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
bit must not be set - If
PhysicalDeviceMutableDescriptorTypeFeaturesEXT
::mutableDescriptorType
is not enabled,pPoolSizes
must not contain adescriptorType
ofDESCRIPTOR_TYPE_MUTABLE_EXT
- If
flags
has theDESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT
bit set,PhysicalDeviceMutableDescriptorTypeFeaturesEXT
::mutableDescriptorType
must be enabled - If
pPoolSizes
contains adescriptorType
ofDESCRIPTOR_TYPE_MUTABLE_EXT
, any otherDESCRIPTOR_TYPE_MUTABLE_EXT
element inpPoolSizes
must not have sets of supported descriptor types which partially overlap
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_DESCRIPTOR_POOL_CREATE_INFO
- Each
pNext
member of any structure (including this one) in thepNext
chain must be eitherNULL
or a pointer to a valid instance ofDescriptorPoolInlineUniformBlockCreateInfo
orMutableDescriptorTypeCreateInfoEXT
- The
sType
value of each struct in thepNext
chain must be unique -
flags
must be a valid combination ofDescriptorPoolCreateFlagBits
values - If
poolSizeCount
is not0
,pPoolSizes
must be a valid pointer to an array ofpoolSizeCount
validDescriptorPoolSize
structures
See Also
VK_VERSION_1_0,
DescriptorPoolCreateFlags
,
DescriptorPoolSize
, StructureType
,
createDescriptorPool
DescriptorPoolCreateInfo | |
|
Instances
data DescriptorSetAllocateInfo (es :: [Type]) Source #
VkDescriptorSetAllocateInfo - Structure specifying the allocation parameters for descriptor sets
Valid Usage
- If the
VK_KHR_maintenance1
extension is not enabled and
PhysicalDeviceProperties
::apiVersion
is less than Vulkan 1.1,descriptorSetCount
must not be greater than the number of sets that are currently available for allocation indescriptorPool
- If the
VK_KHR_maintenance1
extension is not enabled and
PhysicalDeviceProperties
::apiVersion
is less than Vulkan 1.1,descriptorPool
must have enough free descriptor capacity remaining to allocate the descriptor sets of the specified layouts - Each element of
pSetLayouts
must not have been created withDESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR
set - If any element
of
pSetLayouts
was created with theDESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
bit set,descriptorPool
must have been created with theDESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
flag set - If
pSetLayouts
[i] was created with an element ofpBindingFlags
that includesDESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT
, andDescriptorSetVariableDescriptorCountAllocateInfo
is included in thepNext
chain, andDescriptorSetVariableDescriptorCountAllocateInfo
::descriptorSetCount
is not zero, thenDescriptorSetVariableDescriptorCountAllocateInfo
::pDescriptorCounts[i] must be less than or equal toDescriptorSetLayoutBinding
::descriptorCount for the corresponding binding used to createpSetLayouts
[i] - If any element
of
pSetLayouts
was created with theDESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT
bit set,descriptorPool
must have been created with theDESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT
flag set - Each element of
pSetLayouts
must not have been created with theDESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT
bit set
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_DESCRIPTOR_SET_ALLOCATE_INFO
-
pNext
must beNULL
or a pointer to a valid instance ofDescriptorSetVariableDescriptorCountAllocateInfo
- The
sType
value of each struct in thepNext
chain must be unique -
descriptorPool
must be a validDescriptorPool
handle -
pSetLayouts
must be a valid pointer to an array ofdescriptorSetCount
validDescriptorSetLayout
handles -
descriptorSetCount
must be greater than0
- Both of
descriptorPool
, and the elements ofpSetLayouts
must have been created, allocated, or retrieved from the sameDevice
See Also
VK_VERSION_1_0,
DescriptorPool
,
DescriptorSetLayout
,
StructureType
,
allocateDescriptorSets
DescriptorSetAllocateInfo | |
|
Instances
newtype DescriptorSet Source #
VkDescriptorSet - Opaque handle to a descriptor set object
See Also
VK_VERSION_1_0,
CopyDescriptorSet
,
WriteDescriptorSet
,
allocateDescriptorSets
,
cmdBindDescriptorSets
,
freeDescriptorSets
,
getDescriptorSetHostMappingVALVE
,
updateDescriptorSetWithTemplate
,
updateDescriptorSetWithTemplateKHR
Instances
newtype DescriptorSetLayout Source #
VkDescriptorSetLayout - Opaque handle to a descriptor set layout object
See Also
VK_VERSION_1_0,
DescriptorSetAllocateInfo
,
DescriptorSetBindingReferenceVALVE
,
DescriptorUpdateTemplateCreateInfo
,
PipelineLayoutCreateInfo
,
ShaderCreateInfoEXT
,
createDescriptorSetLayout
,
destroyDescriptorSetLayout
,
getDescriptorSetLayoutBindingOffsetEXT
,
getDescriptorSetLayoutSizeEXT
Instances
newtype DescriptorPool Source #
VkDescriptorPool - Opaque handle to a descriptor pool object
See Also
VK_VERSION_1_0,
DescriptorSetAllocateInfo
,
createDescriptorPool
,
destroyDescriptorPool
,
freeDescriptorSets
,
resetDescriptorPool
Instances
newtype DescriptorPoolResetFlags Source #
VkDescriptorPoolResetFlags - Reserved for future use
Description
DescriptorPoolResetFlags
is a bitmask type for setting a mask, but is
currently reserved for future use.
See Also
Instances
newtype DescriptorType Source #
VkDescriptorType - Specifies the type of a descriptor in a descriptor set
Description
DESCRIPTOR_TYPE_SAMPLER
specifies a sampler descriptor.
DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
specifies a combined image sampler descriptor.DESCRIPTOR_TYPE_SAMPLED_IMAGE
specifies a sampled image descriptor.DESCRIPTOR_TYPE_STORAGE_IMAGE
specifies a storage image descriptor.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
specifies a uniform texel buffer descriptor.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
specifies a storage texel buffer descriptor.DESCRIPTOR_TYPE_UNIFORM_BUFFER
specifies a uniform buffer descriptor.DESCRIPTOR_TYPE_STORAGE_BUFFER
specifies a storage buffer descriptor.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
specifies a dynamic uniform buffer descriptor.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
specifies a dynamic storage buffer descriptor.DESCRIPTOR_TYPE_INPUT_ATTACHMENT
specifies an input attachment descriptor.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
specifies an inline uniform block.DESCRIPTOR_TYPE_MUTABLE_EXT
specifies a descriptor of mutable type.DESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM
specifies a sampled weight image descriptor.DESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM
specifies a block matching image descriptor.
When a descriptor set is updated via elements of
WriteDescriptorSet
, members of
pImageInfo
, pBufferInfo
and pTexelBufferView
are only accessed by
the implementation when they correspond to descriptor type being defined
- otherwise they are ignored. The members accessed are as follows for
each descriptor type:
- For
DESCRIPTOR_TYPE_SAMPLER
, only thesampler
member of each element ofWriteDescriptorSet
::pImageInfo
is accessed. - For
DESCRIPTOR_TYPE_SAMPLED_IMAGE
,DESCRIPTOR_TYPE_STORAGE_IMAGE
, orDESCRIPTOR_TYPE_INPUT_ATTACHMENT
, only theimageView
andimageLayout
members of each element ofWriteDescriptorSet
::pImageInfo
are accessed. - For
DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, all members of each element ofWriteDescriptorSet
::pImageInfo
are accessed. - For
DESCRIPTOR_TYPE_UNIFORM_BUFFER
,DESCRIPTOR_TYPE_STORAGE_BUFFER
,DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC
, orDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC
, all members of each element ofWriteDescriptorSet
::pBufferInfo
are accessed. - For
DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
orDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
, each element ofWriteDescriptorSet
::pTexelBufferView
is accessed.
When updating descriptors with a descriptorType
of
DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK
, none of the pImageInfo
,
pBufferInfo
, or pTexelBufferView
members are accessed, instead the
source data of the descriptor update operation is taken from the
WriteDescriptorSetInlineUniformBlock
structure in the pNext
chain of
WriteDescriptorSet
. When updating
descriptors with a descriptorType
of
DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR
, none of the pImageInfo
,
pBufferInfo
, or pTexelBufferView
members are accessed, instead the
source data of the descriptor update operation is taken from the
WriteDescriptorSetAccelerationStructureKHR
structure in the pNext
chain of
WriteDescriptorSet
. When updating
descriptors with a descriptorType
of
DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV
, none of the pImageInfo
,
pBufferInfo
, or pTexelBufferView
members are accessed, instead the
source data of the descriptor update operation is taken from the
WriteDescriptorSetAccelerationStructureNV
structure in the pNext
chain of
WriteDescriptorSet
.
See Also
VK_VERSION_1_0,
DescriptorGetInfoEXT
,
DescriptorPoolSize
,
DescriptorSetLayoutBinding
,
DescriptorUpdateTemplateEntry
,
ImageViewHandleInfoNVX
,
MutableDescriptorTypeListEXT
,
WriteDescriptorSet
Instances
newtype DescriptorPoolCreateFlagBits Source #
VkDescriptorPoolCreateFlagBits - Bitmask specifying certain supported operations on a descriptor pool
See Also
pattern DESCRIPTOR_POOL_CREATE_FREE_DESCRIPTOR_SET_BIT :: DescriptorPoolCreateFlagBits |
|
pattern DESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_POOLS_BIT_NV :: DescriptorPoolCreateFlagBits |
|
pattern DESCRIPTOR_POOL_CREATE_ALLOW_OVERALLOCATION_SETS_BIT_NV :: DescriptorPoolCreateFlagBits |
|
pattern DESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT :: DescriptorPoolCreateFlagBits |
|
pattern DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT :: DescriptorPoolCreateFlagBits |
|
Instances
newtype DescriptorSetLayoutCreateFlagBits Source #
VkDescriptorSetLayoutCreateFlagBits - Bitmask specifying descriptor set layout properties
See Also
pattern DESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT :: DescriptorSetLayoutCreateFlagBits |
|
pattern DESCRIPTOR_SET_LAYOUT_CREATE_INDIRECT_BINDABLE_BIT_NV :: DescriptorSetLayoutCreateFlagBits |
|
pattern DESCRIPTOR_SET_LAYOUT_CREATE_EMBEDDED_IMMUTABLE_SAMPLERS_BIT_EXT :: DescriptorSetLayoutCreateFlagBits |
|
pattern DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT :: DescriptorSetLayoutCreateFlagBits |
|
pattern DESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR :: DescriptorSetLayoutCreateFlagBits |
|
pattern DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT :: DescriptorSetLayoutCreateFlagBits |
|