vulkan-3.6.11: Bindings to the Vulkan graphics API.
Safe HaskellNone
LanguageHaskell2010

Vulkan.Core10.SparseResourceMemoryManagement

Synopsis

Documentation

getImageSparseMemoryRequirements Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the image.

-> Image

image is the Image object to get the memory requirements for.

-> io ("sparseMemoryRequirements" ::: Vector SparseImageMemoryRequirements) 

vkGetImageSparseMemoryRequirements - Query the memory requirements for a sparse image

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 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 MemoryRequirements::size than would be obtained by adding together memory sizes for all SparseImageMemoryRequirements returned by getImageSparseMemoryRequirements. This may occur when the implementation requires unused padding in the address range describing the resource.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • image must be a valid Image 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 SparseImageMemoryRequirements structures
  • image must have been created, allocated, or retrieved from device

See Also

Device, Image, SparseImageMemoryRequirements

getPhysicalDeviceSparseImageFormatProperties Source #

Arguments

:: forall io. MonadIO io 
=> PhysicalDevice

physicalDevice is the physical device from which to query the sparse image capabilities.

-> Format

format is the image format.

-> ImageType

type is the dimensionality of image.

-> ("samples" ::: SampleCountFlagBits)

samples is the number of samples per texel as defined in SampleCountFlagBits.

-> ImageUsageFlags

usage is a bitmask describing the intended usage of the image.

-> ImageTiling

tiling is the tiling arrangement of the texel blocks in memory.

-> io ("properties" ::: Vector SparseImageFormatProperties) 

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

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 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 SparseImageFormatProperties data.

Depth/stencil images with depth and stencil data interleaved into a single plane will return a single SparseImageFormatProperties structure with the aspectMask set to IMAGE_ASPECT_DEPTH_BIT | IMAGE_ASPECT_STENCIL_BIT.

Valid Usage

Valid Usage (Implicit)

  • format must be a valid Format value
  • type must be a valid ImageType value
  • samples must be a valid SampleCountFlagBits value
  • usage must be a valid combination of ImageUsageFlagBits values
  • usage must not be 0
  • tiling must be a valid ImageTiling 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 SparseImageFormatProperties structures

See Also

Format, ImageTiling, ImageType, ImageUsageFlags, PhysicalDevice, SampleCountFlagBits, SparseImageFormatProperties

queueBindSparse Source #

Arguments

:: forall io. MonadIO io 
=> Queue

queue is the queue that the sparse binding operations will be submitted to.

-> ("bindInfo" ::: Vector (SomeStruct BindSparseInfo))

pBindInfo is a pointer to an array of BindSparseInfo structures, each specifying a sparse binding submission batch.

-> Fence

fence is an optional handle to a fence to be signaled. If fence is not NULL_HANDLE, it defines a fence signal operation.

-> io () 

vkQueueBindSparse - Bind device memory to a sparse resource object

Description

queueBindSparse is a queue submission command, with each batch defined by an element of pBindInfo as a BindSparseInfo 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 queueBindSparse 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 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 wait operation referring to a binary semaphore defined by any element of the pWaitSemaphores member of any element of pBindInfo executes on queue, there must be no other queues waiting on the same semaphore
  • All elements of the pWaitSemaphores member of all elements of pBindInfo member referring to a binary semaphore must be semaphores that are signaled, or have semaphore signal operations previously submitted for execution
  • All elements of the pWaitSemaphores member of all elements of pBindInfo created with a SemaphoreType of SEMAPHORE_TYPE_BINARY must reference a semaphore signal operation that has been submitted for execution and any semaphore signal operations on which it depends (if any) must have also been submitted for execution

Valid Usage (Implicit)

  • queue must be a valid Queue handle
  • If bindInfoCount is not 0, pBindInfo must be a valid pointer to an array of bindInfoCount valid BindSparseInfo structures
  • If fence is not NULL_HANDLE, fence must be a valid Fence handle
  • The queue must support sparse binding operations
  • Both of fence, and queue that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to queue 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
Failure

See Also

BindSparseInfo, Fence, Queue

data SparseImageFormatProperties Source #

VkSparseImageFormatProperties - Structure specifying sparse image format properties

See Also

Extent3D, ImageAspectFlags, SparseImageFormatFlags, SparseImageFormatProperties2, SparseImageMemoryRequirements, getPhysicalDeviceSparseImageFormatProperties

Constructors

SparseImageFormatProperties 

Fields

data SparseImageMemoryRequirements Source #

VkSparseImageMemoryRequirements - Structure specifying sparse image memory requirements

See Also

DeviceSize, SparseImageFormatProperties, SparseImageMemoryRequirements2, getImageSparseMemoryRequirements

Constructors

SparseImageMemoryRequirements 

Fields

data ImageSubresource Source #

VkImageSubresource - Structure specifying an image subresource

Valid Usage (Implicit)

See Also

ImageAspectFlags, SparseImageMemoryBind, getImageSubresourceLayout

Constructors

ImageSubresource 

Fields

Instances

Instances details
Eq ImageSubresource Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Show ImageSubresource Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Storable ImageSubresource Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

FromCStruct ImageSubresource Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

ToCStruct ImageSubresource Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Zero ImageSubresource Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

data SparseMemoryBind 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 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 SparseImageMemoryRequirements 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 SparseImageMemoryRequirements::formatProperties.flags contains SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT.

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

Valid Usage

Valid Usage (Implicit)

See Also

DeviceMemory, DeviceSize, SparseBufferMemoryBindInfo, SparseImageOpaqueMemoryBindInfo, SparseMemoryBindFlags

Constructors

SparseMemoryBind 

Fields

Instances

Instances details
Eq SparseMemoryBind Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Show SparseMemoryBind Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Storable SparseMemoryBind Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

FromCStruct SparseMemoryBind Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

ToCStruct SparseMemoryBind Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Zero SparseMemoryBind Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

data SparseImageMemoryBind 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

Valid Usage (Implicit)

See Also

DeviceMemory, DeviceSize, Extent3D, ImageSubresource, Offset3D, SparseImageMemoryBindInfo, SparseMemoryBindFlags

Constructors

SparseImageMemoryBind 

Fields

  • subresource :: ImageSubresource

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

  • offset :: Offset3D

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

  • extent :: Extent3D

    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.

  • memory :: DeviceMemory

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

  • memoryOffset :: DeviceSize

    memoryOffset is an offset into DeviceMemory object. If memory is NULL_HANDLE, this value is ignored.

  • flags :: SparseMemoryBindFlags

    flags are sparse memory binding flags.

data SparseBufferMemoryBindInfo Source #

VkSparseBufferMemoryBindInfo - Structure specifying a sparse buffer memory bind operation

Valid Usage (Implicit)

See Also

BindSparseInfo, Buffer, SparseMemoryBind

Constructors

SparseBufferMemoryBindInfo 

Fields

data SparseImageOpaqueMemoryBindInfo Source #

VkSparseImageOpaqueMemoryBindInfo - Structure specifying sparse image opaque memory bind info

Valid Usage

  • If the flags member of any element of pBinds contains 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 Image handle
  • pBinds must be a valid pointer to an array of bindCount valid SparseMemoryBind structures
  • bindCount must be greater than 0

See Also

BindSparseInfo, Image, SparseMemoryBind

Constructors

SparseImageOpaqueMemoryBindInfo 

Fields

data SparseImageMemoryBindInfo 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 ImageCreateInfo when image was created

Valid Usage (Implicit)

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

See Also

BindSparseInfo, Image, SparseImageMemoryBind

Constructors

SparseImageMemoryBindInfo 

Fields

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

VkBindSparseInfo - Structure specifying a sparse binding operation

Valid Usage

Valid Usage (Implicit)

  • Each pNext member of any structure (including this one) in the pNext chain must be either NULL or a pointer to a valid instance of DeviceGroupBindSparseInfo or TimelineSemaphoreSubmitInfo
  • The sType value of each struct in the pNext chain must be unique
  • If waitSemaphoreCount is not 0, pWaitSemaphores must be a valid pointer to an array of waitSemaphoreCount valid Semaphore handles
  • If bufferBindCount is not 0, pBufferBinds must be a valid pointer to an array of bufferBindCount valid SparseBufferMemoryBindInfo structures
  • If imageOpaqueBindCount is not 0, pImageOpaqueBinds must be a valid pointer to an array of imageOpaqueBindCount valid SparseImageOpaqueMemoryBindInfo structures
  • If imageBindCount is not 0, pImageBinds must be a valid pointer to an array of imageBindCount valid SparseImageMemoryBindInfo structures
  • If signalSemaphoreCount is not 0, pSignalSemaphores must be a valid pointer to an array of signalSemaphoreCount valid Semaphore handles
  • Both of the elements of pSignalSemaphores, and the elements of pWaitSemaphores that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

See Also

Semaphore, SparseBufferMemoryBindInfo, SparseImageMemoryBindInfo, SparseImageOpaqueMemoryBindInfo, StructureType, queueBindSparse

Constructors

BindSparseInfo 

Fields

Instances

Instances details
Extensible BindSparseInfo Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). BindSparseInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). BindSparseInfo ds -> Chain es -> BindSparseInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends BindSparseInfo e => b) -> Maybe b Source #

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

Defined in Vulkan.Core10.SparseResourceMemoryManagement

(Extendss BindSparseInfo es, PeekChain es) => FromCStruct (BindSparseInfo es) Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

(Extendss BindSparseInfo es, PokeChain es) => ToCStruct (BindSparseInfo es) Source # 
Instance details

Defined in Vulkan.Core10.SparseResourceMemoryManagement

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

Defined in Vulkan.Core10.SparseResourceMemoryManagement

newtype ImageAspectFlagBits Source #

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

See Also

BindImagePlaneMemoryInfo, ImageAspectFlags, ImagePlaneMemoryRequirementsInfo

Instances

Instances details
Eq ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Ord ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Read ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Show ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Storable ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Bits ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Zero ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

newtype SparseImageFormatFlagBits Source #

VkSparseImageFormatFlagBits - Bitmask specifying additional information about a sparse image resource

See Also

SparseImageFormatFlags

Bundled Patterns

pattern SPARSE_IMAGE_FORMAT_SINGLE_MIPTAIL_BIT :: SparseImageFormatFlagBits

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

pattern SPARSE_IMAGE_FORMAT_ALIGNED_MIP_SIZE_BIT :: SparseImageFormatFlagBits

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 SPARSE_IMAGE_FORMAT_NONSTANDARD_BLOCK_SIZE_BIT :: SparseImageFormatFlagBits

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.

Instances

Instances details
Eq SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

Ord SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

Read SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

Show SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

Storable SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

Bits SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

Methods

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

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

xor :: SparseImageFormatFlagBits -> SparseImageFormatFlagBits -> SparseImageFormatFlagBits #

complement :: SparseImageFormatFlagBits -> SparseImageFormatFlagBits #

shift :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

rotate :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

zeroBits :: SparseImageFormatFlagBits #

bit :: Int -> SparseImageFormatFlagBits #

setBit :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

clearBit :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

complementBit :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

testBit :: SparseImageFormatFlagBits -> Int -> Bool #

bitSizeMaybe :: SparseImageFormatFlagBits -> Maybe Int #

bitSize :: SparseImageFormatFlagBits -> Int #

isSigned :: SparseImageFormatFlagBits -> Bool #

shiftL :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

unsafeShiftL :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

shiftR :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

unsafeShiftR :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

rotateL :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

rotateR :: SparseImageFormatFlagBits -> Int -> SparseImageFormatFlagBits #

popCount :: SparseImageFormatFlagBits -> Int #

Zero SparseImageFormatFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseImageFormatFlagBits

newtype SparseMemoryBindFlagBits Source #

VkSparseMemoryBindFlagBits - Bitmask specifying usage of a sparse memory binding operation

See Also

SparseMemoryBindFlags

Bundled Patterns

pattern SPARSE_MEMORY_BIND_METADATA_BIT :: SparseMemoryBindFlagBits

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

Instances

Instances details
Eq SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits

Ord SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits

Read SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits

Show SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits

Storable SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits

Bits SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits

Zero SparseMemoryBindFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.SparseMemoryBindFlagBits