vulkan-3.0.0.0: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Core10.DescriptorSet

Synopsis

Documentation

createDescriptorSetLayout :: PokeChain a => Device -> DescriptorSetLayoutCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> IO DescriptorSetLayout Source #

vkCreateDescriptorSetLayout - Create a new descriptor set layout

Parameters

  • Device is the logical device that creates the descriptor set layout.
  • pCreateInfo is a pointer to a DescriptorSetLayoutCreateInfo structure specifying the state of the descriptor set layout object.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pSetLayout is a pointer to a DescriptorSetLayout handle in which the resulting descriptor set layout object is returned.

Valid Usage (Implicit)

Return Codes

Success
Failure

See Also

AllocationCallbacks, DescriptorSetLayout, DescriptorSetLayoutCreateInfo, Device

withDescriptorSetLayout :: PokeChain a => Device -> DescriptorSetLayoutCreateInfo a -> Maybe AllocationCallbacks -> (DescriptorSetLayout -> IO r) -> IO r Source #

A safe wrapper for createDescriptorSetLayout and destroyDescriptorSetLayout using bracket

The allocated value must not be returned from the provided computation

destroyDescriptorSetLayout :: Device -> DescriptorSetLayout -> ("allocator" ::: Maybe AllocationCallbacks) -> IO () Source #

vkDestroyDescriptorSetLayout - Destroy a descriptor set layout object

Parameters

  • Device is the logical device that destroys the descriptor set layout.

Valid Usage

Valid Usage (Implicit)

Host Synchronization

See Also

AllocationCallbacks, DescriptorSetLayout, Device

createDescriptorPool :: PokeChain a => Device -> DescriptorPoolCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> IO DescriptorPool Source #

vkCreateDescriptorPool - Creates a descriptor pool object

Parameters

  • Device is the logical device that creates the descriptor pool.
  • pCreateInfo is a pointer to a DescriptorPoolCreateInfo structure specifying the state of the descriptor pool object.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pDescriptorPool is a pointer to a DescriptorPool handle in which the resulting descriptor pool object is returned.

Description

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

The created descriptor pool is returned in pDescriptorPool.

Valid Usage (Implicit)

Return Codes

Success
Failure

See Also

AllocationCallbacks, DescriptorPool, DescriptorPoolCreateInfo, Device

withDescriptorPool :: PokeChain a => Device -> DescriptorPoolCreateInfo a -> Maybe AllocationCallbacks -> (DescriptorPool -> IO r) -> IO r Source #

A safe wrapper for createDescriptorPool and destroyDescriptorPool using bracket

The allocated value must not be returned from the provided computation

destroyDescriptorPool :: Device -> DescriptorPool -> ("allocator" ::: Maybe AllocationCallbacks) -> IO () Source #

vkDestroyDescriptorPool - Destroy a descriptor pool object

Parameters

  • Device is the logical device that destroys the descriptor pool.

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

Valid Usage (Implicit)

Host Synchronization

See Also

AllocationCallbacks, DescriptorPool, Device

resetDescriptorPool :: Device -> DescriptorPool -> DescriptorPoolResetFlags -> IO () Source #

vkResetDescriptorPool - Resets a descriptor pool object

Parameters

  • Device is the logical device that owns the descriptor pool.

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

  • All uses of DescriptorPool (via any allocated descriptor sets) must have completed execution

Valid Usage (Implicit)

Host Synchronization

Return Codes

Success

See Also

DescriptorPool, DescriptorPoolResetFlags, Device

allocateDescriptorSets :: PokeChain a => Device -> DescriptorSetAllocateInfo a -> IO ("descriptorSets" ::: Vector DescriptorSet) Source #

vkAllocateDescriptorSets - Allocate one or more descriptor sets

Parameters

  • Device is the logical device that owns the descriptor pool.
  • pAllocateInfo is a pointer to a DescriptorSetAllocateInfo structure describing parameters of the allocation.
  • pDescriptorSets is a pointer to an array of DescriptorSet handles in which the resulting descriptor set objects are returned.

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. Descriptors also become undefined if the underlying resource is destroyed. Descriptor sets containing undefined descriptors can still be bound and used, subject to the following conditions:

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 member 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 DescriptorPoolInlineUniformBlockCreateInfoEXT::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)

  • pAllocateInfo must be a valid pointer to a valid DescriptorSetAllocateInfo structure
  • pDescriptorSets must be a valid pointer to an array of pAllocateInfo::descriptorSetCount DescriptorSet handles
  • The value referenced by pAllocateInfo::descriptorSetCount must be greater than 0

Host Synchronization

  • Host access to pAllocateInfo::descriptorPool must be externally synchronized

Return Codes

Success
Failure

See Also

DescriptorSet, DescriptorSetAllocateInfo, Device

withDescriptorSets :: PokeChain a => Device -> DescriptorSetAllocateInfo a -> (Vector DescriptorSet -> IO r) -> IO r Source #

A safe wrapper for allocateDescriptorSets and freeDescriptorSets using bracket

The allocated value must not be returned from the provided computation

freeDescriptorSets :: Device -> DescriptorPool -> ("descriptorSets" ::: Vector DescriptorSet) -> IO () Source #

vkFreeDescriptorSets - Free one or more descriptor sets

Parameters

  • Device is the logical device that owns the descriptor pool.
  • DescriptorPool is the descriptor pool from which the descriptor sets were allocated.
  • descriptorSetCount is the number of elements in the pDescriptorSets array.
  • pDescriptorSets is a pointer to an array of handles to DescriptorSet objects.

Description

After calling freeDescriptorSets, all descriptor sets in pDescriptorSets are invalid.

Valid Usage

  • All submitted commands that refer to any element of pDescriptorSets must have completed execution

Valid Usage (Implicit)

Host Synchronization

  • Host access to each member of pDescriptorSets must be externally synchronized

Return Codes

Success

See Also

DescriptorPool, DescriptorSet, Device

updateDescriptorSets :: PokeChain a => Device -> ("descriptorWrites" ::: Vector (WriteDescriptorSet a)) -> ("descriptorCopies" ::: Vector CopyDescriptorSet) -> IO () Source #

vkUpdateDescriptorSets - Update the contents of a descriptor set object

Parameters

  • Device is the logical device that updates the descriptor sets.
  • descriptorWriteCount is the number of elements in the pDescriptorWrites array.
  • pDescriptorWrites is a pointer to an array of WriteDescriptorSet structures describing the descriptor sets to write to.
  • descriptorCopyCount is the number of elements in the pDescriptorCopies array.
  • pDescriptorCopies is a pointer to an array of CopyDescriptorSet structures describing the descriptor sets to copy between.

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

Valid Usage (Implicit)

  • If descriptorWriteCount is not 0, pDescriptorWrites must be a valid pointer to an array of descriptorWriteCount valid WriteDescriptorSet structures
  • If descriptorCopyCount is not 0, pDescriptorCopies must be a valid pointer to an array of descriptorCopyCount valid CopyDescriptorSet structures

Host Synchronization

  • Host access to pDescriptorWrites[].dstSet must be externally synchronized
  • Host access to pDescriptorCopies[].dstSet must be externally synchronized

See Also

CopyDescriptorSet, Device, WriteDescriptorSet

data DescriptorBufferInfo Source #

VkDescriptorBufferInfo - Structure specifying descriptor buffer info

Description

Note

When setting range to WHOLE_SIZE, the effective range must not be larger than the maximum range for the descriptor type (maxUniformBufferRange or maxStorageBufferRange). This means that WHOLE_SIZE is not typically useful in the common case where uniform buffer descriptors are suballocated from a buffer that is much larger than maxUniformBufferRange.

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.

Valid Usage

  • offset must be less than the size of Buffer
  • If range is not equal to WHOLE_SIZE, range must be greater than 0
  • If range is not equal to WHOLE_SIZE, range must be less than or equal to the size of Buffer minus offset

Valid Usage (Implicit)

See Also

Buffer, DeviceSize, WriteDescriptorSet

Constructors

DescriptorBufferInfo 

Fields

  • buffer :: Buffer

    Buffer is the buffer resource.

  • offset :: DeviceSize

    offset is the offset in bytes from the start of Buffer. Access to buffer memory via this descriptor uses addressing that is relative to this starting offset.

  • range :: DeviceSize

    range is the size in bytes that is used for this descriptor update, or WHOLE_SIZE to use the range from offset to the end of the buffer.

Instances
Show DescriptorBufferInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Storable DescriptorBufferInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

FromCStruct DescriptorBufferInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

ToCStruct DescriptorBufferInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Zero DescriptorBufferInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

data DescriptorImageInfo Source #

VkDescriptorImageInfo - Structure specifying descriptor image info

Description

Members of DescriptorImageInfo that are not used in an update (as described above) are ignored.

Valid Usage

  • ImageView must not be 2D or 2D array image view created from a 3D image

Valid Usage (Implicit)

  • Both of ImageView, and Sampler that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

See Also

ImageLayout, ImageView, Sampler, WriteDescriptorSet

Constructors

DescriptorImageInfo 

Fields

Instances
Show DescriptorImageInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Storable DescriptorImageInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

FromCStruct DescriptorImageInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

ToCStruct DescriptorImageInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Zero DescriptorImageInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

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_EXT, in which case the source data for the descriptor writes is taken from the WriteDescriptorSetInlineUniformBlockEXT structure included 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 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.

Note

The same behavior applies to bindings with a descriptor type of DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT 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 of binding of all DescriptorSetLayoutBinding structures specified when dstSet’s descriptor set layout was created

Valid Usage (Implicit)

See Also

BufferView, DescriptorBufferInfo, DescriptorImageInfo, DescriptorSet, DescriptorType, StructureType, cmdPushDescriptorSetKHR, updateDescriptorSets

Constructors

WriteDescriptorSet 

Fields

Instances
Extensible WriteDescriptorSet Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Show (Chain es) => Show (WriteDescriptorSet es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PeekChain es => FromCStruct (WriteDescriptorSet es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PokeChain es => ToCStruct (WriteDescriptorSet es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

es ~ ([] :: [Type]) => Zero (WriteDescriptorSet es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

data CopyDescriptorSet Source #

VkCopyDescriptorSet - Structure specifying a copy descriptor set operation

Valid Usage

  • srcBinding must be a valid binding within srcSet

Valid Usage (Implicit)

  • pNext must be NULL
  • srcSet must be a valid DescriptorSet handle
  • dstSet must be a valid DescriptorSet handle
  • Both of dstSet, and srcSet must have been created, allocated, or retrieved from the same Device

See Also

DescriptorSet, StructureType, updateDescriptorSets

Constructors

CopyDescriptorSet 

Fields

  • srcSet :: DescriptorSet

    srcSet, srcBinding, and srcArrayElement are the source set, binding, and array element, respectively. If the descriptor binding identified by srcSet and srcBinding has a descriptor type of DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT then srcArrayElement specifies the starting byte offset within the binding to copy from.

  • srcBinding :: Word32
     
  • srcArrayElement :: Word32
     
  • dstSet :: DescriptorSet

    dstSet, dstBinding, and dstArrayElement are the destination set, binding, and array element, respectively. If the descriptor binding identified by dstSet and dstBinding has a descriptor type of DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT then dstArrayElement specifies the starting byte offset within the binding to copy to.

  • dstBinding :: Word32
     
  • dstArrayElement :: Word32
     
  • descriptorCount :: Word32

    descriptorCount is the number of descriptors to copy from the source to destination. If descriptorCount is greater than the number of remaining array elements in the source or destination binding, those affect consecutive bindings in a manner similar to WriteDescriptorSet above. If the descriptor binding identified by srcSet and srcBinding has a descriptor type of DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT then descriptorCount specifies the number of bytes to copy and the remaining array elements in the source or destination binding refer to the remaining number of bytes in those.

Instances
Show CopyDescriptorSet Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Storable CopyDescriptorSet Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

FromCStruct CopyDescriptorSet Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

ToCStruct CopyDescriptorSet Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Zero CopyDescriptorSet Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

data DescriptorSetLayoutBinding Source #

VkDescriptorSetLayoutBinding - Structure specifying a descriptor set layout binding

Description

  • pImmutableSamplers affects initialization of samplers. If DescriptorType specifies a DESCRIPTOR_TYPE_SAMPLER or DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER type descriptor, then pImmutableSamplers can be used to initialize a set of immutable samplers. Immutable samplers are permanently bound into the set layout and must not be changed; updating a DESCRIPTOR_TYPE_SAMPLER descriptor with immutable samplers is not allowed and updates to a DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER descriptor with immutable samplers does not modify the samplers (the image views are updated, but the sampler updates are ignored). If pImmutableSamplers is not NULL, then it points to an array of sampler handles that will be copied into the set layout and used for the corresponding binding. Only the sampler handles are copied; the sampler objects must not be destroyed before the final use of the set layout and any descriptor pools and sets created using it. If pImmutableSamplers is NULL, then the sampler slots are dynamic and sampler handles must be bound into descriptor sets using this layout. If DescriptorType is not one of these descriptor types, then pImmutableSamplers is ignored.

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

Valid Usage (Implicit)

See Also

DescriptorSetLayoutCreateInfo, DescriptorType, Sampler, ShaderStageFlags

Constructors

DescriptorSetLayoutBinding 

Fields

  • binding :: Word32

    binding is the binding number of this entry and corresponds to a resource of the same binding number in the shader stages.

  • descriptorType :: DescriptorType

    DescriptorType is a DescriptorType specifying which type of resource descriptors are used for this binding.

  • stageFlags :: ShaderStageFlags

    stageFlags member is a bitmask of ShaderStageFlagBits specifying which pipeline shader stages can access a resource for this binding. SHADER_STAGE_ALL is a shorthand specifying that all defined shader stages, including any additional stages defined by extensions, can access the resource.

    If a shader stage is not included in stageFlags, then a resource must not be accessed from that stage via this binding within any pipeline using the set layout. Other than input attachments which are limited to the fragment shader, there are no limitations on what combinations of stages can use a descriptor binding, and in particular a binding can be used by both graphics stages and the compute stage.

  • immutableSamplers :: Either Word32 (Vector Sampler)
     

data DescriptorSetLayoutCreateInfo (es :: [Type]) Source #

VkDescriptorSetLayoutCreateInfo - Structure specifying parameters of a newly created descriptor set layout

Valid Usage

Valid Usage (Implicit)

See Also

DescriptorSetLayoutBinding, DescriptorSetLayoutCreateFlags, StructureType, createDescriptorSetLayout, getDescriptorSetLayoutSupport, getDescriptorSetLayoutSupportKHR

Constructors

DescriptorSetLayoutCreateInfo 

Fields

Instances
Extensible DescriptorSetLayoutCreateInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Show (Chain es) => Show (DescriptorSetLayoutCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PeekChain es => FromCStruct (DescriptorSetLayoutCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PokeChain es => ToCStruct (DescriptorSetLayoutCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

es ~ ([] :: [Type]) => Zero (DescriptorSetLayoutCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

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

  • descriptorCount must be greater than 0

Valid Usage (Implicit)

See Also

DescriptorPoolCreateInfo, DescriptorType

Constructors

DescriptorPoolSize 

Fields

Instances
Show DescriptorPoolSize Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Storable DescriptorPoolSize Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

FromCStruct DescriptorPoolSize Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

ToCStruct DescriptorPoolSize Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Zero DescriptorPoolSize Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

data DescriptorPoolCreateInfo (es :: [Type]) Source #

VkDescriptorPoolCreateInfo - Structure specifying parameters of a newly created descriptor pool

Description

If multiple DescriptorPoolSize structures 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.

Valid Usage

  • maxSets must be greater than 0

Valid Usage (Implicit)

See Also

DescriptorPoolCreateFlags, DescriptorPoolSize, StructureType, createDescriptorPool

Constructors

DescriptorPoolCreateInfo 

Fields

Instances
Extensible DescriptorPoolCreateInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Show (Chain es) => Show (DescriptorPoolCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PeekChain es => FromCStruct (DescriptorPoolCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PokeChain es => ToCStruct (DescriptorPoolCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

es ~ ([] :: [Type]) => Zero (DescriptorPoolCreateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

data DescriptorSetAllocateInfo (es :: [Type]) Source #

VkDescriptorSetAllocateInfo - Structure specifying the allocation parameters for descriptor sets

Valid Usage

Valid Usage (Implicit)

See Also

DescriptorPool, DescriptorSetLayout, StructureType, allocateDescriptorSets

Constructors

DescriptorSetAllocateInfo 

Fields

Instances
Extensible DescriptorSetAllocateInfo Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

Show (Chain es) => Show (DescriptorSetAllocateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PeekChain es => FromCStruct (DescriptorSetAllocateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

PokeChain es => ToCStruct (DescriptorSetAllocateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet

es ~ ([] :: [Type]) => Zero (DescriptorSetAllocateInfo es) Source # 
Instance details

Defined in Graphics.Vulkan.Core10.DescriptorSet