vulkan-2.0.0.1: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Core10.SparseResourceMemoryManagement

Synopsis

Documentation

newtype VkImageAspectFlagBits Source #

VkImageAspectFlagBits - Bitmask specifying which aspects of an image are included in a view

See Also

VkBindImagePlaneMemoryInfo, VkImageAspectFlags, VkImagePlaneMemoryRequirementsInfo

Instances
Eq VkImageAspectFlagBits Source # 
Instance details
Ord VkImageAspectFlagBits Source # 
Instance details
Read VkImageAspectFlagBits Source # 
Instance details
Show VkImageAspectFlagBits Source # 
Instance details
Storable VkImageAspectFlagBits Source # 
Instance details
Bits VkImageAspectFlagBits Source # 
Instance details
FiniteBits VkImageAspectFlagBits Source # 
Instance details

pattern VK_IMAGE_ASPECT_COLOR_BIT :: VkImageAspectFlagBits Source #

VK_IMAGE_ASPECT_COLOR_BIT specifies the color aspect.

pattern VK_IMAGE_ASPECT_DEPTH_BIT :: VkImageAspectFlagBits Source #

VK_IMAGE_ASPECT_DEPTH_BIT specifies the depth aspect.

pattern VK_IMAGE_ASPECT_STENCIL_BIT :: VkImageAspectFlagBits Source #

VK_IMAGE_ASPECT_STENCIL_BIT specifies the stencil aspect.

pattern VK_IMAGE_ASPECT_METADATA_BIT :: VkImageAspectFlagBits Source #

VK_IMAGE_ASPECT_METADATA_BIT specifies the metadata aspect, used for sparse sparse resource operations.

newtype VkSparseMemoryBindFlagBits Source #

VkSparseMemoryBindFlagBits - Bitmask specifying usage of a sparse memory binding operation

See Also

VkSparseMemoryBindFlags

Instances
Eq VkSparseMemoryBindFlagBits Source # 
Instance details
Ord VkSparseMemoryBindFlagBits Source # 
Instance details
Read VkSparseMemoryBindFlagBits Source # 
Instance details
Show VkSparseMemoryBindFlagBits Source # 
Instance details
Storable VkSparseMemoryBindFlagBits Source # 
Instance details
Bits VkSparseMemoryBindFlagBits Source # 
Instance details

Methods

(.&.) :: VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits #

(.|.) :: VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits #

xor :: VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits #

complement :: VkSparseMemoryBindFlagBits -> VkSparseMemoryBindFlagBits #

shift :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

rotate :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

zeroBits :: VkSparseMemoryBindFlagBits #

bit :: Int -> VkSparseMemoryBindFlagBits #

setBit :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

clearBit :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

complementBit :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

testBit :: VkSparseMemoryBindFlagBits -> Int -> Bool #

bitSizeMaybe :: VkSparseMemoryBindFlagBits -> Maybe Int #

bitSize :: VkSparseMemoryBindFlagBits -> Int #

isSigned :: VkSparseMemoryBindFlagBits -> Bool #

shiftL :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

unsafeShiftL :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

shiftR :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

unsafeShiftR :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

rotateL :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

rotateR :: VkSparseMemoryBindFlagBits -> Int -> VkSparseMemoryBindFlagBits #

popCount :: VkSparseMemoryBindFlagBits -> Int #

FiniteBits VkSparseMemoryBindFlagBits Source # 
Instance details

pattern VK_SPARSE_MEMORY_BIND_METADATA_BIT :: VkSparseMemoryBindFlagBits Source #

VK_SPARSE_MEMORY_BIND_METADATA_BIT specifies that the memory being bound is only for the metadata aspect.

newtype VkSparseImageFormatFlagBits Source #

VkSparseImageFormatFlagBits - Bitmask specifying additional information about a sparse image resource

See Also

VkSparseImageFormatFlags

Instances
Eq VkSparseImageFormatFlagBits Source # 
Instance details
Ord VkSparseImageFormatFlagBits Source # 
Instance details
Read VkSparseImageFormatFlagBits Source # 
Instance details
Show VkSparseImageFormatFlagBits Source # 
Instance details
Storable VkSparseImageFormatFlagBits Source # 
Instance details
Bits VkSparseImageFormatFlagBits Source # 
Instance details

Methods

(.&.) :: VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits #

(.|.) :: VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits #

xor :: VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits #

complement :: VkSparseImageFormatFlagBits -> VkSparseImageFormatFlagBits #

shift :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

rotate :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

zeroBits :: VkSparseImageFormatFlagBits #

bit :: Int -> VkSparseImageFormatFlagBits #

setBit :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

clearBit :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

complementBit :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

testBit :: VkSparseImageFormatFlagBits -> Int -> Bool #

bitSizeMaybe :: VkSparseImageFormatFlagBits -> Maybe Int #

bitSize :: VkSparseImageFormatFlagBits -> Int #

isSigned :: VkSparseImageFormatFlagBits -> Bool #

shiftL :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

unsafeShiftL :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

shiftR :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

unsafeShiftR :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

rotateL :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

rotateR :: VkSparseImageFormatFlagBits -> Int -> VkSparseImageFormatFlagBits #

popCount :: VkSparseImageFormatFlagBits -> Int #

FiniteBits VkSparseImageFormatFlagBits Source # 
Instance details

pattern VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT :: VkSparseImageFormatFlagBits Source #

VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT specifies that the image uses a single mip tail region for all array layers.

pattern VK_SPARSE_IMAGE_FORMAT_ALIGNED_MIP_SIZE_BIT :: VkSparseImageFormatFlagBits Source #

VK_SPARSE_IMAGE_FORMAT_ALIGNED_MIP_SIZE_BIT specifies that the first mip level whose dimensions are not integer multiples of the corresponding dimensions of the sparse image block begins the mip tail region.

pattern VK_SPARSE_IMAGE_FORMAT_NONSTANDARD_BLOCK_SIZE_BIT :: VkSparseImageFormatFlagBits Source #

VK_SPARSE_IMAGE_FORMAT_NONSTANDARD_BLOCK_SIZE_BIT specifies that the image uses non-standard sparse image block dimensions, and the imageGranularity values do not match the standard sparse image block dimensions for the given format.

vkGetImageSparseMemoryRequirements :: ("device" ::: VkDevice) -> ("image" ::: VkImage) -> ("pSparseMemoryRequirementCount" ::: Ptr Word32) -> ("pSparseMemoryRequirements" ::: Ptr VkSparseImageMemoryRequirements) -> IO () Source #

vkGetImageSparseMemoryRequirements - Query the memory requirements for a sparse image

Parameters

  • device is the logical device that owns the image.
  • image is the VkImage object to get the memory requirements for.
  • pSparseMemoryRequirementCount is a pointer to an integer related to the number of sparse memory requirements available or queried, as described below.
  • pSparseMemoryRequirements is either NULL or a pointer to an array of VkSparseImageMemoryRequirements structures.

Description

If pSparseMemoryRequirements is NULL, then the number of sparse memory requirements available is returned in pSparseMemoryRequirementCount. Otherwise, pSparseMemoryRequirementCount must point to a variable set by the user to the number of elements in the pSparseMemoryRequirements array, and on return the variable is overwritten with the number of structures actually written to pSparseMemoryRequirements. If pSparseMemoryRequirementCount is less than the number of sparse memory requirements available, at most pSparseMemoryRequirementCount structures will be written.

If the image was not created with VK_IMAGE_CREATE_SPARSE_RESIDENCY_BIT then pSparseMemoryRequirementCount will be set to zero and pSparseMemoryRequirements will not be written to.

Note

It is legal for an implementation to report a larger value in VkMemoryRequirements::size than would be obtained by adding together memory sizes for all VkSparseImageMemoryRequirements returned by vkGetImageSparseMemoryRequirements. This may occur when the implementation requires unused padding in the address range describing the resource.

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • image must be a valid VkImage handle
  • pSparseMemoryRequirementCount must be a valid pointer to a uint32_t value
  • If the value referenced by pSparseMemoryRequirementCount is not 0, and pSparseMemoryRequirements is not NULL, pSparseMemoryRequirements must be a valid pointer to an array of pSparseMemoryRequirementCount VkSparseImageMemoryRequirements structures
  • image must have been created, allocated, or retrieved from device

See Also

VkDevice, VkImage, VkSparseImageMemoryRequirements

vkGetPhysicalDeviceSparseImageFormatProperties :: ("physicalDevice" ::: VkPhysicalDevice) -> ("format" ::: VkFormat) -> ("type" ::: VkImageType) -> ("samples" ::: VkSampleCountFlagBits) -> ("usage" ::: VkImageUsageFlags) -> ("tiling" ::: VkImageTiling) -> ("pPropertyCount" ::: Ptr Word32) -> ("pProperties" ::: Ptr VkSparseImageFormatProperties) -> IO () Source #

vkGetPhysicalDeviceSparseImageFormatProperties - Retrieve properties of an image format applied to sparse images

Parameters

  • physicalDevice is the physical device from which to query the sparse image capabilities.
  • format is the image format.
  • type is the dimensionality of image.
  • samples is the number of samples per texel as defined in VkSampleCountFlagBits.
  • usage is a bitmask describing the intended usage of the image.
  • tiling is the tiling arrangement of the data elements in memory.
  • pPropertyCount is a pointer to an integer related to the number of sparse format properties available or queried, as described below.
  • pProperties is either NULL or a pointer to an array of VkSparseImageFormatProperties structures.

Description

If pProperties is NULL, then the number of sparse format properties available is returned in pPropertyCount. Otherwise, pPropertyCount must point to a variable set by the user to the number of elements in the pProperties array, and on return the variable is overwritten with the number of structures actually written to pProperties. If pPropertyCount is less than the number of sparse format properties available, at most pPropertyCount structures will be written.

If VK_IMAGE_CREATE_SPARSE_RESIDENCY_BIT is not supported for the given arguments, pPropertyCount will be set to zero upon return, and no data will be written to pProperties.

Multiple aspects are returned for depth/stencil images that are implemented as separate planes by the implementation. The depth and stencil data planes each have unique VkSparseImageFormatProperties data.

Depth/stencil images with depth and stencil data interleaved into a single plane will return a single VkSparseImageFormatProperties structure with the aspectMask set to VK_IMAGE_ASPECT_DEPTH_BIT | VK_IMAGE_ASPECT_STENCIL_BIT.

Valid Usage

  • samples must be a bit value that is set in VkImageFormatProperties::sampleCounts returned by vkGetPhysicalDeviceImageFormatProperties with format, type, tiling, and usage equal to those in this command and flags equal to the value that is set in VkImageCreateInfo::flags when the image is created

Valid Usage (Implicit)

  • physicalDevice must be a valid VkPhysicalDevice handle
  • format must be a valid VkFormat value
  • type must be a valid VkImageType value
  • samples must be a valid VkSampleCountFlagBits value
  • usage must be a valid combination of VkImageUsageFlagBits values
  • usage must not be 0
  • tiling must be a valid VkImageTiling value
  • pPropertyCount must be a valid pointer to a uint32_t value
  • If the value referenced by pPropertyCount is not 0, and pProperties is not NULL, pProperties must be a valid pointer to an array of pPropertyCount VkSparseImageFormatProperties structures

See Also

VkFormat, VkImageTiling, VkImageType, VkImageUsageFlags, VkPhysicalDevice, VkSampleCountFlagBits, VkSparseImageFormatProperties

vkQueueBindSparse :: ("queue" ::: VkQueue) -> ("bindInfoCount" ::: Word32) -> ("pBindInfo" ::: Ptr VkBindSparseInfo) -> ("fence" ::: VkFence) -> IO VkResult Source #

vkQueueBindSparse - Bind device memory to a sparse resource object

Parameters

  • queue is the queue that the sparse binding operations will be submitted to.
  • bindInfoCount is the number of elements in the pBindInfo array.
  • pBindInfo is an array of VkBindSparseInfo structures, each specifying a sparse binding submission batch.
  • fence is an optional handle to a fence to be signaled. If fence is not VK_NULL_HANDLE, it defines a fence signal operation.

Description

vkQueueBindSparse is a queue submission command, with each batch defined by an element of pBindInfo as an instance of the VkBindSparseInfo structure. Batches begin execution in the order they appear in pBindInfo, but may complete out of order.

Within a batch, a given range of a resource must not be bound more than once. Across batches, if a range is to be bound to one allocation and offset and then to another allocation and offset, then the application must guarantee (usually using semaphores) that the binding operations are executed in the correct order, as well as to order binding operations against the execution of command buffer submissions.

As no operation to vkQueueBindSparse causes any pipeline stage to access memory, synchronization primitives used in this command effectively only define execution dependencies.

Additional information about fence and semaphore operation is described in the synchronization chapter.

Valid Usage

  • If fence is not VK_NULL_HANDLE, fence must not be associated with any other queue command that has not yet completed execution on that queue
  • Each element of the pSignalSemaphores member of each element of pBindInfo must be unsignaled when the semaphore signal operation it defines is executed on the device
  • When a semaphore unsignal operation defined by any element of the pWaitSemaphores member of any element of pBindInfo executes on queue, no other queue must be waiting on the same semaphore.
  • All elements of the pWaitSemaphores member of all elements of pBindInfo must be semaphores that are signaled, or have semaphore signal operations previously submitted for execution.

Valid Usage (Implicit)

  • queue must be a valid VkQueue handle
  • If bindInfoCount is not 0, pBindInfo must be a valid pointer to an array of bindInfoCount valid VkBindSparseInfo structures
  • If fence is not VK_NULL_HANDLE, fence must be a valid VkFence handle
  • The queue must support sparse binding operations
  • Both of fence, and queue that are valid handles must have been created, allocated, or retrieved from the same VkDevice

Host Synchronization

  • Host access to queue must be externally synchronized
  • Host access to pBindInfo[].pWaitSemaphores[] must be externally synchronized
  • Host access to pBindInfo[].pSignalSemaphores[] must be externally synchronized
  • Host access to pBindInfo[].pBufferBinds[].buffer must be externally synchronized
  • Host access to pBindInfo[].pImageOpaqueBinds[].image must be externally synchronized
  • Host access to pBindInfo[].pImageBinds[].image must be externally synchronized
  • Host access to fence must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
- - SPARSE_BINDING -

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY
  • VK_ERROR_DEVICE_LOST

See Also

VkBindSparseInfo, VkFence, VkQueue

data VkOffset3D Source #

VkOffset3D - Structure specifying a three-dimensional offset

See Also

VkBufferImageCopy, VkImageBlit, VkImageCopy, VkImageResolve, VkSparseImageMemoryBind

Constructors

VkOffset3D 

Fields

data VkSparseImageFormatProperties Source #

Constructors

VkSparseImageFormatProperties 

Fields

data VkSparseImageMemoryRequirements Source #

VkSparseImageMemoryRequirements - Structure specifying sparse image memory requirements

Members

  • formatProperties.aspectMask is the set of aspects of the image that this sparse memory requirement applies to. This will usually have a single aspect specified. However, depth/stencil images may have depth and stencil data interleaved in the same sparse block, in which case both VK_IMAGE_ASPECT_DEPTH_BIT and VK_IMAGE_ASPECT_STENCIL_BIT would be present.
  • formatProperties.imageGranularity describes the dimensions of a single bindable sparse image block in texel units. For aspect VK_IMAGE_ASPECT_METADATA_BIT, all dimensions will be zero. All metadata is located in the mip tail region.
  • formatProperties.flags is a bitmask of VkSparseImageFormatFlagBits:

    • If VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT is set the image uses a single mip tail region for all array layers.
    • If VK_SPARSE_IMAGE_FORMAT_ALIGNED_MIP_SIZE_BIT is set the dimensions of mip levels must be integer multiples of the corresponding dimensions of the sparse image block for levels not located in the mip tail.
    • If VK_SPARSE_IMAGE_FORMAT_NONSTANDARD_BLOCK_SIZE_BIT is set the image uses non-standard sparse image block dimensions. The formatProperties.imageGranularity values do not match the standard sparse image block dimension corresponding to the image’s format.
  • imageMipTailFirstLod is the first mip level at which image subresources are included in the mip tail region.
  • imageMipTailSize is the memory size (in bytes) of the mip tail region. If formatProperties.flags contains VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT, this is the size of the whole mip tail, otherwise this is the size of the mip tail of a single array layer. This value is guaranteed to be a multiple of the sparse block size in bytes.
  • imageMipTailOffset is the opaque memory offset used with VkSparseImageOpaqueMemoryBindInfo to bind the mip tail region(s).
  • imageMipTailStride is the offset stride between each array-layer’s mip tail, if formatProperties.flags does not contain VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT (otherwise the value is undefined).

See Also

VkDeviceSize, VkSparseImageFormatProperties, VkSparseImageMemoryRequirements2, vkGetImageSparseMemoryRequirements

data VkImageSubresource Source #

VkImageSubresource - Structure specifying a image subresource

Valid Usage (Implicit)

  • aspectMask must not be 0

See Also

VkImageAspectFlags, VkSparseImageMemoryBind, vkGetImageSubresourceLayout

Constructors

VkImageSubresource 

Fields

data VkSparseMemoryBind Source #

VkSparseMemoryBind - Structure specifying a sparse memory bind operation

Description

The binding range [resourceOffset, resourceOffset + size) has different constraints based on flags. If flags contains VK_SPARSE_MEMORY_BIND_METADATA_BIT, the binding range must be within the mip tail region of the metadata aspect. This metadata region is defined by:

  • metadataRegion = [base, base + imageMipTailSize)
  • base = imageMipTailOffset + imageMipTailStride × n

and imageMipTailOffset, imageMipTailSize, and imageMipTailStride values are from the VkSparseImageMemoryRequirements corresponding to the metadata aspect of the image, and n is a valid array layer index for the image,

imageMipTailStride is considered to be zero for aspects where VkSparseImageMemoryRequirements::formatProperties.flags contains VK_SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT.

If flags does not contain VK_SPARSE_MEMORY_BIND_METADATA_BIT, the binding range must be within the range [0,VkMemoryRequirements::size).

Valid Usage

  • If memory is not VK_NULL_HANDLE, memory must not have been created with a memory type that reports VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT bit set
  • size must be greater than 0
  • resourceOffset must be less than the size of the resource
  • size must be less than or equal to the size of the resource minus resourceOffset
  • memoryOffset must be less than the size of memory
  • size must be less than or equal to the size of memory minus memoryOffset

Valid Usage (Implicit)

  • If memory is not VK_NULL_HANDLE, memory must be a valid VkDeviceMemory handle

See Also

VkDeviceMemory, VkDeviceSize, VkSparseBufferMemoryBindInfo, VkSparseImageOpaqueMemoryBindInfo, VkSparseMemoryBindFlags

Constructors

VkSparseMemoryBind 

Fields

data VkSparseImageMemoryBind Source #

VkSparseImageMemoryBind - Structure specifying sparse image memory bind

Valid Usage

  • If the sparse aliased residency feature is not enabled, and if any other resources are bound to ranges of memory, the range of memory being bound must not overlap with those bound ranges
  • memory and memoryOffset must match the memory requirements of the calling command’s image, as described in section {html_spec_relative}#resources-association
  • subresource must be a valid image subresource for image (see {html_spec_relative}#resources-image-views)
  • offset.x must be a multiple of the sparse image block width (VkSparseImageFormatProperties::imageGranularity.width) of the image
  • extent.width must either be a multiple of the sparse image block width of the image, or else (extent.width + offset.x) must equal the width of the image subresource
  • offset.y must be a multiple of the sparse image block height (VkSparseImageFormatProperties::imageGranularity.height) of the image
  • extent.height must either be a multiple of the sparse image block height of the image, or else (extent.height + offset.y) must equal the height of the image subresource
  • offset.z must be a multiple of the sparse image block depth (VkSparseImageFormatProperties::imageGranularity.depth) of the image
  • extent.depth must either be a multiple of the sparse image block depth of the image, or else (extent.depth + offset.z) must equal the depth of the image subresource

Valid Usage (Implicit)

  • subresource must be a valid VkImageSubresource structure

See Also

VkDeviceMemory, VkDeviceSize, VkExtent3D, VkImageSubresource, VkOffset3D, VkSparseImageMemoryBindInfo, VkSparseMemoryBindFlags

Constructors

VkSparseImageMemoryBind 

Fields

  • vkSubresource :: VkImageSubresource

    subresource is the aspectMask and region of interest in the image.

  • vkOffset :: VkOffset3D

    offset are the coordinates of the first texel within the image subresource to bind.

  • vkExtent :: VkExtent3D

    extent is the size in texels of the region within the image subresource to bind. The extent must be a multiple of the sparse image block dimensions, except when binding sparse image blocks along the edge of an image subresource it can instead be such that any coordinate of offset + extent equals the corresponding dimensions of the image subresource.

  • vkMemory :: VkDeviceMemory

    memory is the VkDeviceMemory object that the sparse image blocks of the image are bound to. If memory is VK_NULL_HANDLE, the sparse image blocks are unbound.

  • vkMemoryOffset :: VkDeviceSize

    memoryOffset is an offset into VkDeviceMemory object. If memory is VK_NULL_HANDLE, this value is ignored.

  • vkFlags :: VkSparseMemoryBindFlags

    flags are sparse memory binding flags.

data VkSparseBufferMemoryBindInfo Source #

VkSparseBufferMemoryBindInfo - Structure specifying a sparse buffer memory bind operation

Valid Usage (Implicit)

  • buffer must be a valid VkBuffer handle
  • pBinds must be a valid pointer to an array of bindCount valid VkSparseMemoryBind structures
  • bindCount must be greater than 0

See Also

VkBindSparseInfo, VkBuffer, VkSparseMemoryBind

Constructors

VkSparseBufferMemoryBindInfo 

Fields

data VkSparseImageOpaqueMemoryBindInfo Source #

VkSparseImageOpaqueMemoryBindInfo - Structure specifying sparse image opaque memory bind info

Valid Usage

  • If the flags member of any element of pBinds contains VK_SPARSE_MEMORY_BIND_METADATA_BIT, the binding range defined must be within the mip tail region of the metadata aspect of image

Valid Usage (Implicit)

  • image must be a valid VkImage handle
  • pBinds must be a valid pointer to an array of bindCount valid VkSparseMemoryBind structures
  • bindCount must be greater than 0

See Also

VkBindSparseInfo, VkImage, VkSparseMemoryBind

Constructors

VkSparseImageOpaqueMemoryBindInfo 

Fields

data VkSparseImageMemoryBindInfo Source #

VkSparseImageMemoryBindInfo - Structure specifying sparse image memory bind info

Valid Usage

  • The subresource.mipLevel member of each element of pBinds must be less than the mipLevels specified in VkImageCreateInfo when image was created
  • The subresource.arrayLayer member of each element of pBinds must be less than the arrayLayers specified in VkImageCreateInfo when image was created

Valid Usage (Implicit)

  • image must be a valid VkImage handle
  • pBinds must be a valid pointer to an array of bindCount valid VkSparseImageMemoryBind structures
  • bindCount must be greater than 0

See Also

VkBindSparseInfo, VkImage, VkSparseImageMemoryBind

Constructors

VkSparseImageMemoryBindInfo 

Fields

data VkBindSparseInfo Source #

VkBindSparseInfo - Structure specifying a sparse binding operation

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_BIND_SPARSE_INFO
  • pNext must be NULL or a pointer to a valid instance of VkDeviceGroupBindSparseInfo
  • If waitSemaphoreCount is not 0, pWaitSemaphores must be a valid pointer to an array of waitSemaphoreCount valid VkSemaphore handles
  • If bufferBindCount is not 0, pBufferBinds must be a valid pointer to an array of bufferBindCount valid VkSparseBufferMemoryBindInfo structures
  • If imageOpaqueBindCount is not 0, pImageOpaqueBinds must be a valid pointer to an array of imageOpaqueBindCount valid VkSparseImageOpaqueMemoryBindInfo structures
  • If imageBindCount is not 0, pImageBinds must be a valid pointer to an array of imageBindCount valid VkSparseImageMemoryBindInfo structures
  • If signalSemaphoreCount is not 0, pSignalSemaphores must be a valid pointer to an array of signalSemaphoreCount valid VkSemaphore handles
  • Both of the elements of pSignalSemaphores, and the elements of pWaitSemaphores that are valid handles must have been created, allocated, or retrieved from the same VkDevice

See Also

VkSemaphore, VkSparseBufferMemoryBindInfo, VkSparseImageMemoryBindInfo, VkSparseImageOpaqueMemoryBindInfo, VkStructureType, vkQueueBindSparse

Constructors

VkBindSparseInfo 

Fields

type VkImageAspectFlags = VkImageAspectFlagBits Source #

VkImageAspectFlags - Bitmask of VkImageAspectFlagBits

Description

VkImageAspectFlags is a bitmask type for setting a mask of zero or more VkImageAspectFlagBits.

See Also

VkClearAttachment, VkImageAspectFlagBits, VkImageSubresource, VkImageSubresourceLayers, VkImageSubresourceRange, VkInputAttachmentAspectReference, VkSparseImageFormatProperties

type VkSparseMemoryBindFlags = VkSparseMemoryBindFlagBits Source #

VkSparseMemoryBindFlags - Bitmask of VkSparseMemoryBindFlagBits

Description

VkSparseMemoryBindFlags is a bitmask type for setting a mask of zero or more VkSparseMemoryBindFlagBits.

See Also

VkSparseImageMemoryBind, VkSparseMemoryBind, VkSparseMemoryBindFlagBits

type VkSparseImageFormatFlags = VkSparseImageFormatFlagBits Source #

VkSparseImageFormatFlags - Bitmask of VkSparseImageFormatFlagBits

Description

VkSparseImageFormatFlags is a bitmask type for setting a mask of zero or more VkSparseImageFormatFlagBits.

See Also

VkSparseImageFormatFlagBits, VkSparseImageFormatProperties