Safe Haskell | None |
---|---|
Language | Haskell2010 |
Name
VK_KHR_synchronization2 - device extension
VK_KHR_synchronization2
- Name String
VK_KHR_synchronization2
- Extension Type
- Device extension
- Registered Extension Number
- 315
- Revision
- 1
- Extension and Version Dependencies
- Requires Vulkan 1.0
- Requires
VK_KHR_get_physical_device_properties2
- Contact
Other Extension Metadata
- Last Modified Date
- 2020-12-03
- Interactions and External Dependencies
- Interacts with
VK_KHR_create_renderpass2
- Interacts with
- Contributors
- Tobias Hector
Description
This extension modifies the original core synchronization APIs to simplify the interface and improve usability of these APIs. It also adds new pipeline stage and access flag types that extend into the 64-bit range, as we have run out within the 32-bit range. The new flags are identical to the old values within the 32-bit range, with new stages and bits beyond that.
Pipeline stages and access flags are now specified together in memory
barrier structures, making the connection between the two more obvious.
Additionally, scoping the pipeline stages into the barrier structs
allows the use of the MEMORY_READ
and MEMORY_WRITE
flags without
sacrificing precision. The per-stage access flags should be used to
disambiguate specific accesses in a given stage or set of stages - for
instance, between uniform reads and sampling operations.
Layout transitions have been simplified as well; rather than requiring a
different set of layouts for depth/stencil/color attachments, there
are generic
IMAGE_LAYOUT_ATTACHMENT_OPTIMAL_KHR
and IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR
layouts which are contextually applied based on the image format. For
example, for a depth format image,
IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR
is
equivalent to
IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL_KHR
.
IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR
also functionally replaces
IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL
.
Events are now more efficient, because they include memory dependency information when you set them on the device. Previously, this information was only known when waiting on an event, so the dependencies could not be satisfied until the wait occurred. That sometimes meant stalling the pipeline when the wait occurred. The new API provides enough information for implementations to satisfy these dependencies in parallel with other tasks.
Queue submission has been changed to wrap command buffers and semaphores
in extensible structures, which incorporate changes from Vulkan 1.1,
VK_KHR_device_group
, and VK_KHR_timeline_semaphore
. This also adds a
pipeline stage to the semaphore signal operation, mirroring the existing
pipeline stage specification for wait operations.
Other miscellaneous changes include:
- Events can now be specified as interacting only with the device, allowing more efficient access to the underlying object.
Image memory barriers that do not perform an image layout transition can be specified by setting
oldLayout
equal tonewLayout
.- E.g. the old and new layout can both be set to
IMAGE_LAYOUT_UNDEFINED
, without discarding data in the image.
- E.g. the old and new layout can both be set to
- Queue family ownership transfer parameters are simplified in some cases.
- Where two synchronization commands need to be matched up (queue transfer operations, events), the dependency information specified in each place must now match completely for consistency.
- Extensions with commands or functions with a
PipelineStageFlags
orPipelineStageFlagBits
parameter have had those APIs replaced with equivalents usingPipelineStageFlags2KHR
. - The new event and barrier interfaces are now more extensible for future changes.
- Relevant pipeline stage masks can now be specified as empty with the
new
PIPELINE_STAGE_NONE_KHR
andPIPELINE_STAGE_2_NONE_KHR
values. MemoryBarrier2KHR
can be chained toSubpassDependency2
, overriding the original 32-bit stage and access masks.
New Base Types
New Commands
If VK_AMD_buffer_marker is supported:
If VK_NV_device_diagnostic_checkpoints is supported:
New Structures
CommandBufferSubmitInfoKHR
DependencyInfoKHR
ImageMemoryBarrier2KHR
SemaphoreSubmitInfoKHR
SubmitInfo2KHR
Extending
PhysicalDeviceFeatures2
,DeviceCreateInfo
:Extending
SubpassDependency2
:
If VK_NV_device_diagnostic_checkpoints is supported:
New Enums
New Bitmasks
New Enum Constants
KHR_SYNCHRONIZATION_2_SPEC_VERSION
Extending
AccessFlagBits
:Extending
EventCreateFlagBits
:Extending
ImageLayout
:Extending
PipelineStageFlagBits
:Extending
StructureType
:STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER_2_KHR
STRUCTURE_TYPE_COMMAND_BUFFER_SUBMIT_INFO_KHR
STRUCTURE_TYPE_DEPENDENCY_INFO_KHR
STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER_2_KHR
STRUCTURE_TYPE_MEMORY_BARRIER_2_KHR
STRUCTURE_TYPE_PHYSICAL_DEVICE_SYNCHRONIZATION_2_FEATURES_KHR
STRUCTURE_TYPE_SEMAPHORE_SUBMIT_INFO_KHR
STRUCTURE_TYPE_SUBMIT_INFO_2_KHR
If VK_EXT_blend_operation_advanced is supported:
If VK_EXT_conditional_rendering is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_EXT_fragment_density_map is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_EXT_transform_feedback is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_KHR_acceleration_structure is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_KHR_fragment_shading_rate is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_KHR_ray_tracing_pipeline is supported:
If VK_NV_device_diagnostic_checkpoints is supported:
Extending
StructureType
:
If VK_NV_device_generated_commands is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_NV_mesh_shader is supported:
Extending
PipelineStageFlagBits2KHR
:
If VK_NV_ray_tracing is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
If VK_NV_shading_rate_image is supported:
Extending
AccessFlagBits2KHR
:Extending
PipelineStageFlagBits2KHR
:
Examples
See https://github.com/KhronosGroup/Vulkan-Docs/wiki/Synchronization-Examples
Version History
Revision 1, 2020-12-03 (Tobias Hector)
- Internal revisions
See Also
AccessFlagBits2KHR
, AccessFlags2KHR
, BufferMemoryBarrier2KHR
,
CommandBufferSubmitInfoKHR
, DependencyInfoKHR
,
Flags64
, ImageMemoryBarrier2KHR
,
MemoryBarrier2KHR
, PhysicalDeviceSynchronization2FeaturesKHR
,
PipelineStageFlagBits2KHR
, PipelineStageFlags2KHR
,
SemaphoreSubmitInfoKHR
, SubmitFlagBitsKHR
, SubmitFlagsKHR
,
SubmitInfo2KHR
, cmdPipelineBarrier2KHR
, cmdResetEvent2KHR
,
cmdSetEvent2KHR
, cmdWaitEvents2KHR
, cmdWriteTimestamp2KHR
,
queueSubmit2KHR
Document Notes
For more information, see the Vulkan Specification
This page is a generated document. Fixes and changes should be made to the generator scripts, not directly.
Synopsis
- cmdSetEvent2KHR :: forall io. MonadIO io => CommandBuffer -> Event -> DependencyInfoKHR -> io ()
- cmdResetEvent2KHR :: forall io. MonadIO io => CommandBuffer -> Event -> ("stageMask" ::: PipelineStageFlags2KHR) -> io ()
- cmdWaitEvents2KHR :: forall io. MonadIO io => CommandBuffer -> ("events" ::: Vector Event) -> ("dependencyInfos" ::: Vector DependencyInfoKHR) -> io ()
- cmdWaitEvents2KHRSafe :: forall io. MonadIO io => CommandBuffer -> ("events" ::: Vector Event) -> ("dependencyInfos" ::: Vector DependencyInfoKHR) -> io ()
- cmdPipelineBarrier2KHR :: forall io. MonadIO io => CommandBuffer -> DependencyInfoKHR -> io ()
- queueSubmit2KHR :: forall io. MonadIO io => Queue -> ("submits" ::: Vector (SomeStruct SubmitInfo2KHR)) -> Fence -> io ()
- cmdWriteTimestamp2KHR :: forall io. MonadIO io => CommandBuffer -> PipelineStageFlags2KHR -> QueryPool -> ("query" ::: Word32) -> io ()
- cmdWriteBufferMarker2AMD :: forall io. MonadIO io => CommandBuffer -> PipelineStageFlags2KHR -> ("dstBuffer" ::: Buffer) -> ("dstOffset" ::: DeviceSize) -> ("marker" ::: Word32) -> io ()
- getQueueCheckpointData2NV :: forall io. MonadIO io => Queue -> io ("checkpointData" ::: Vector CheckpointData2NV)
- pattern PIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV :: PipelineStageFlagBits2KHR
- pattern ACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV :: AccessFlagBits2KHR
- pattern PIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_NV :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_NV :: PipelineStageFlagBits2KHR
- pattern ACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_NV :: AccessFlagBits2KHR
- pattern ACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_NV :: AccessFlagBits2KHR
- pattern PIPELINE_STAGE_2_TRANSFER_BIT_KHR :: PipelineStageFlagBits2KHR
- data MemoryBarrier2KHR = MemoryBarrier2KHR {}
- data ImageMemoryBarrier2KHR (es :: [Type]) = ImageMemoryBarrier2KHR {
- next :: Chain es
- srcStageMask :: PipelineStageFlags2KHR
- srcAccessMask :: AccessFlags2KHR
- dstStageMask :: PipelineStageFlags2KHR
- dstAccessMask :: AccessFlags2KHR
- oldLayout :: ImageLayout
- newLayout :: ImageLayout
- srcQueueFamilyIndex :: Word32
- dstQueueFamilyIndex :: Word32
- image :: Image
- subresourceRange :: ImageSubresourceRange
- data BufferMemoryBarrier2KHR = BufferMemoryBarrier2KHR {}
- data DependencyInfoKHR = DependencyInfoKHR {}
- data SemaphoreSubmitInfoKHR = SemaphoreSubmitInfoKHR {}
- data CommandBufferSubmitInfoKHR = CommandBufferSubmitInfoKHR {}
- data SubmitInfo2KHR (es :: [Type]) = SubmitInfo2KHR {}
- data QueueFamilyCheckpointProperties2NV = QueueFamilyCheckpointProperties2NV {}
- data CheckpointData2NV = CheckpointData2NV {}
- data PhysicalDeviceSynchronization2FeaturesKHR = PhysicalDeviceSynchronization2FeaturesKHR {}
- type AccessFlags2KHR = AccessFlagBits2KHR
- newtype AccessFlagBits2KHR where
- AccessFlagBits2KHR Flags64
- pattern ACCESS_2_NONE_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_INDEX_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_UNIFORM_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_SHADER_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_SHADER_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_TRANSFER_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_TRANSFER_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_HOST_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_HOST_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_MEMORY_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_MEMORY_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_SHADER_SAMPLED_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_SHADER_STORAGE_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI :: AccessFlagBits2KHR
- pattern ACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT :: AccessFlagBits2KHR
- pattern ACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT :: AccessFlagBits2KHR
- pattern ACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_FRAGMENT_SHADING_RATE_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR
- pattern ACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV :: AccessFlagBits2KHR
- pattern ACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV :: AccessFlagBits2KHR
- pattern ACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT :: AccessFlagBits2KHR
- pattern ACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT :: AccessFlagBits2KHR
- pattern ACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT :: AccessFlagBits2KHR
- pattern ACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT :: AccessFlagBits2KHR
- type PipelineStageFlags2KHR = PipelineStageFlagBits2KHR
- newtype PipelineStageFlagBits2KHR where
- PipelineStageFlagBits2KHR Flags64
- pattern PIPELINE_STAGE_2_NONE_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_TOP_OF_PIPE_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_VERTEX_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_COMPUTE_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_BOTTOM_OF_PIPE_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_HOST_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_COPY_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_RESOLVE_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_BLIT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_CLEAR_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_PRE_RASTERIZATION_SHADERS_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_MESH_SHADER_BIT_NV :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_TASK_SHADER_BIT_NV :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT :: PipelineStageFlagBits2KHR
- pattern PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT :: PipelineStageFlagBits2KHR
- type SubmitFlagsKHR = SubmitFlagBitsKHR
- newtype SubmitFlagBitsKHR where
- type KHR_SYNCHRONIZATION_2_SPEC_VERSION = 1
- pattern KHR_SYNCHRONIZATION_2_SPEC_VERSION :: forall a. Integral a => a
- type KHR_SYNCHRONIZATION_2_EXTENSION_NAME = "VK_KHR_synchronization2"
- pattern KHR_SYNCHRONIZATION_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
- type Flags64 = Word64
Documentation
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> Event |
|
-> DependencyInfoKHR |
|
-> io () |
vkCmdSetEvent2KHR - Set an event object to signaled state
Description
When cmdSetEvent2KHR
is submitted to a queue, it defines the first
half of memory dependencies defined by pDependencyInfo
, as well as an
event signal operation which sets the event to the signaled state. A
memory dependency is defined between the event signal operation and
commands that occur earlier in submission order.
The first
synchronization scope
and
access scope
are defined by the union of all the memory dependencies defined by
pDependencyInfo
, and are applied to all operations that occur earlier
in
submission order.
Queue family ownership transfers
and
image layout transitions
defined by pDependencyInfo
are also included in the first scopes.
The second
synchronization scope
includes only the event signal operation, and any
queue family ownership transfers
and
image layout transitions
defined by pDependencyInfo
.
The second access scope includes only queue family ownership transfers and image layout transitions.
Future cmdWaitEvents2KHR
commands rely on all values of each element
in pDependencyInfo
matching exactly with those used to signal the
corresponding event. cmdWaitEvents
must not be used to wait on the result of a signal operation defined
by cmdSetEvent2KHR
.
Note
The extra information provided by cmdSetEvent2KHR
compared to
cmdSetEvent
allows implementations
to more efficiently schedule the operations required to satisfy the
requested dependencies. With
cmdSetEvent
, the full dependency
information is not known until
cmdWaitEvents
is recorded, forcing
implementations to insert the required operations at that point and not
before.
If event
is already in the signaled state when cmdSetEvent2KHR
is
executed on the device, then cmdSetEvent2KHR
has no effect, no event
signal operation occurs, and no dependency is generated.
Valid Usage
- The synchronization2 feature must be enabled
- The
dependencyFlags
member ofpDependencyInfo
must be0
- The current device mask
of
commandBuffer
must include exactly one physical device - The
srcStageMask
member of any element of thepMemoryBarriers
,pBufferMemoryBarriers
, orpImageMemoryBarriers
members ofpDependencyInfo
must only include pipeline stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from - The
dstStageMask
member of any element of thepMemoryBarriers
,pBufferMemoryBarriers
, orpImageMemoryBarriers
members ofpDependencyInfo
must only include pipeline stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from
Valid Usage (Implicit)
-
commandBuffer
must be a validCommandBuffer
handle
-
event
must be a validEvent
handle -
pDependencyInfo
must be a valid pointer to a validDependencyInfoKHR
structure -
commandBuffer
must be in the recording state - The
CommandPool
thatcommandBuffer
was allocated from must support graphics, or compute operations - This command must only be called outside of a render pass instance
- Both of
commandBuffer
, andevent
must have been created, allocated, or retrieved from the sameDevice
Host Synchronization
- Host access to
commandBuffer
must be externally synchronized
- Host access to the
CommandPool
thatcommandBuffer
was allocated from must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
Primary Secondary | Outside | Graphics Compute |
See Also
VK_KHR_synchronization2,
CommandBuffer
, DependencyInfoKHR
,
Event
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> Event |
|
-> ("stageMask" ::: PipelineStageFlags2KHR) |
|
-> io () |
vkCmdResetEvent2KHR - Reset an event object to non-signaled state
Description
When cmdResetEvent2KHR
is submitted to a queue, it defines an
execution dependency on commands that were submitted before it, and
defines an event unsignal operation which resets the event to the
unsignaled state.
The first
synchronization scope
includes all commands that occur earlier in
submission order.
The synchronization scope is limited to operations by stageMask
or
stages that are
logically earlier
than stageMask
.
The second synchronization scope includes only the event unsignal operation.
If event
is already in the unsignaled state when cmdResetEvent2KHR
is executed on the device, then this command has no effect, no event
unsignal operation occurs, and no execution dependency is generated.
Valid Usage
- If the
geometry shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- The synchronization2 feature must be enabled
-
stageMask
must not includePIPELINE_STAGE_2_HOST_BIT_KHR
- There must be an execution
dependency between
cmdResetEvent2KHR
and the execution of anycmdWaitEvents
that includesevent
in itspEvents
parameter - There must be an execution
dependency between
cmdResetEvent2KHR
and the execution of anycmdWaitEvents2KHR
that includesevent
in itspEvents
parameter -
commandBuffer
’s current device mask must include exactly one physical device
Valid Usage (Implicit)
-
commandBuffer
must be a validCommandBuffer
handle
-
event
must be a validEvent
handle -
stageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
stageMask
must not be0
-
commandBuffer
must be in the recording state - The
CommandPool
thatcommandBuffer
was allocated from must support graphics, or compute operations - This command must only be called outside of a render pass instance
- Both of
commandBuffer
, andevent
must have been created, allocated, or retrieved from the sameDevice
Host Synchronization
- Host access to
commandBuffer
must be externally synchronized
- Host access to the
CommandPool
thatcommandBuffer
was allocated from must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
Primary Secondary | Outside | Graphics Compute |
See Also
VK_KHR_synchronization2,
CommandBuffer
, Event
,
PipelineStageFlags2KHR
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> ("events" ::: Vector Event) |
|
-> ("dependencyInfos" ::: Vector DependencyInfoKHR) |
|
-> io () |
vkCmdWaitEvents2KHR - Wait for one or more events
Description
When cmdWaitEvents2KHR
is submitted to a queue, it inserts memory
dependencies according to the elements of pDependencyInfos
and each
corresponding element of pEvents
. cmdWaitEvents2KHR
must not be
used to wait on event signal operations occurring on other queues, or
signal operations execyted by
cmdSetEvent
.
The first
synchronization scope
and
access scope
of each memory dependency defined by any element i of pDependencyInfos
are applied to operations that occurred earlier in
submission order
than the last event signal operation on element i of pEvents
.
Signal operations for an event at index i are only included if:
- The event was signaled by a
cmdSetEvent2KHR
command that occurred earlier in submission order with adependencyInfo
parameter exactly equal to the element ofpDependencyInfos
at index i ; or - The event was created without
EVENT_CREATE_DEVICE_ONLY_BIT_KHR
, and the first synchronization scope defined by the element ofpDependencyInfos
at index i only includes host operations (PIPELINE_STAGE_2_HOST_BIT_KHR
).
The second
synchronization scope
and
access scope
of each memory dependency defined by any element i of pDependencyInfos
are applied to operations that occurred later in
submission order
than cmdWaitEvents2KHR
.
Note
cmdWaitEvents2KHR
is used with cmdSetEvent2KHR
to define a memory
dependency between two sets of action commands, roughly in the same way
as pipeline barriers, but split into two commands such that work between
the two may execute unhindered.
Note
Applications should be careful to avoid race conditions when using
events. There is no direct ordering guarantee between cmdSetEvent2KHR
and cmdResetEvent2KHR
,
cmdResetEvent
, or
cmdSetEvent
. Another execution
dependency (e.g. a pipeline barrier or semaphore with
PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
) is needed to prevent such a
race condition.
Valid Usage
- The synchronization2 feature must be enabled
- Members of
pEvents
must not have been signaled bycmdSetEvent
- For any element i of
pEvents
, if that event is signaled bycmdSetEvent2KHR
, that command’sdependencyInfo
parameter must be exactly equal to the ith element ofpDependencyInfos
- For any element i of
pEvents
, if that event is signaled bysetEvent
, barriers in the ith element ofpDependencyInfos
must include only host operations in their first synchronization scope - For any element i of
pEvents
, if barriers in the ith element ofpDependencyInfos
include only host operations, the ith element ofpEvents
must be signaled beforecmdWaitEvents2KHR
is executed - For any element i of
pEvents
, if barriers in the ith element ofpDependencyInfos
do not include host operations, the ith element ofpEvents
must be signaled by a correspondingcmdSetEvent2KHR
that occurred earlier in submission order - The
srcStageMask
member of any element of thepMemoryBarriers
,pBufferMemoryBarriers
, orpImageMemoryBarriers
members ofpDependencyInfos
must either include only pipeline stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from, or include onlyPIPELINE_STAGE_2_HOST_BIT_KHR
- The
dstStageMask
member of any element of thepMemoryBarriers
,pBufferMemoryBarriers
, orpImageMemoryBarriers
members ofpDependencyInfos
must only include pipeline stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from - The
dependencyFlags
member of any element ofpDependencyInfo
must be0
- If
pEvents
includes one or more events that will be signaled bysetEvent
aftercommandBuffer
has been submitted to a queue, thencmdWaitEvents2KHR
must not be called inside a render pass instance -
commandBuffer
’s current device mask must include exactly one physical device
Valid Usage (Implicit)
-
commandBuffer
must be a validCommandBuffer
handle
-
pEvents
must be a valid pointer to an array ofeventCount
validEvent
handles -
pDependencyInfos
must be a valid pointer to an array ofeventCount
validDependencyInfoKHR
structures -
commandBuffer
must be in the recording state - The
CommandPool
thatcommandBuffer
was allocated from must support graphics, or compute operations -
eventCount
must be greater than0
- Both of
commandBuffer
, and the elements ofpEvents
must have been created, allocated, or retrieved from the sameDevice
Host Synchronization
- Host access to
commandBuffer
must be externally synchronized
- Host access to the
CommandPool
thatcommandBuffer
was allocated from must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
Primary Secondary | Both | Graphics Compute |
See Also
VK_KHR_synchronization2,
CommandBuffer
, DependencyInfoKHR
,
Event
cmdWaitEvents2KHRSafe Source #
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> ("events" ::: Vector Event) |
|
-> ("dependencyInfos" ::: Vector DependencyInfoKHR) |
|
-> io () |
A variant of cmdWaitEvents2KHR
which makes a *safe* FFI call
cmdPipelineBarrier2KHR Source #
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> DependencyInfoKHR |
|
-> io () |
vkCmdPipelineBarrier2KHR - Insert a memory dependency
Description
When cmdPipelineBarrier2KHR
is submitted to a queue, it defines memory
dependencies between commands that were submitted before it, and those
submitted after it.
The first
synchronization scope
and
access scope
of each memory dependency defined by any element i of pDependencyInfos
are applied to operations that occurred earlier in
submission order.
The second
synchronization scope
and
access scope
of each memory dependency defined by any element i of pDependencyInfos
are applied to operations that occurred later in
submission order.
If cmdPipelineBarrier2KHR
is recorded within a render pass instance,
the synchronization scopes are
limited to operations within the same subpass.
Valid Usage
- If
cmdPipelineBarrier2KHR
is called within a render pass instance, the render pass must have been created with at least oneSubpassDependency
instance inRenderPassCreateInfo
::pDependencies
that expresses a dependency from the current subpass to itself, with synchronization scopes and access scopes that are all supersets of the scopes defined in this command
- If
cmdPipelineBarrier2KHR
is called within a render pass instance, it must not include any buffer memory barriers - If
cmdPipelineBarrier2KHR
is called within a render pass instance, theimage
member of any image memory barrier included in this command must be an attachment used in the current subpass both as an input attachment, and as either a color or depth/stencil attachment - If
cmdPipelineBarrier2KHR
is called within a render pass instance, theoldLayout
andnewLayout
members of any image memory barrier included in this command must be equal - If
cmdPipelineBarrier2KHR
is called within a render pass instance, thesrcQueueFamilyIndex
anddstQueueFamilyIndex
members of any image memory barrier included in this command must be equal - If
cmdPipelineBarrier2KHR
is called outside of a render pass instance,DEPENDENCY_VIEW_LOCAL_BIT
must not be included in the dependency flags - If
cmdPipelineBarrier2KHR
is called within a render pass instance, the render pass must not have been started withcmdBeginRenderingKHR
- The synchronization2 feature must be enabled
- The
srcStageMask
member of any element of thepMemoryBarriers
,pBufferMemoryBarriers
, orpImageMemoryBarriers
members ofpDependencyInfo
must only include pipeline stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from - The
dstStageMask
member of any element of thepMemoryBarriers
,pBufferMemoryBarriers
, orpImageMemoryBarriers
members ofpDependencyInfo
must only include pipeline stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from
Valid Usage (Implicit)
-
commandBuffer
must be a validCommandBuffer
handle
-
pDependencyInfo
must be a valid pointer to a validDependencyInfoKHR
structure -
commandBuffer
must be in the recording state - The
CommandPool
thatcommandBuffer
was allocated from must support transfer, graphics, or compute operations
Host Synchronization
- Host access to
commandBuffer
must be externally synchronized
- Host access to the
CommandPool
thatcommandBuffer
was allocated from must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
Primary Secondary | Both | Transfer Graphics Compute |
See Also
:: forall io. MonadIO io | |
=> Queue |
|
-> ("submits" ::: Vector (SomeStruct SubmitInfo2KHR)) |
|
-> Fence |
|
-> io () |
vkQueueSubmit2KHR - Submits command buffers to a queue
Description
queueSubmit2KHR
is a
queue submission command,
with each batch defined by an element of pSubmits
.
Semaphore operations submitted with queueSubmit2KHR
have additional
ordering constraints compared to other submission commands, with
dependencies involving previous and subsequent queue operations.
Information about these additional constraints can be found in the
semaphore
section of
the synchronization chapter.
If any command buffer submitted to this queue is in the
executable state,
it is moved to the
pending state.
Once execution of all submissions of a command buffer complete, it moves
from the
pending state,
back to the
executable state.
If a command buffer was recorded with the
COMMAND_BUFFER_USAGE_ONE_TIME_SUBMIT_BIT
flag, it instead moves back to the
invalid state.
If queueSubmit2KHR
fails, it may return
ERROR_OUT_OF_HOST_MEMORY
or
ERROR_OUT_OF_DEVICE_MEMORY
. If it does, the
implementation must ensure that the state and contents of any
resources or synchronization primitives referenced by the submitted
command buffers and any semaphores referenced by pSubmits
is
unaffected by the call or its failure. If queueSubmit2KHR
fails in
such a way that the implementation is unable to make that guarantee, the
implementation must return
ERROR_DEVICE_LOST
. See
Lost Device.
Valid Usage
- If
fence
is notNULL_HANDLE
,fence
must be unsignaled
- If
fence
is notNULL_HANDLE
,fence
must not be associated with any other queue command that has not yet completed execution on that queue - The synchronization2 feature must be enabled
- If a command recorded
into the
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
referenced anEvent
, that event must not be referenced by a command that has been submitted to another queue and is still in the pending state - The
semaphore
member of any binary semaphore element of thepSignalSemaphoreInfos
member of any element ofpSubmits
must be unsignaled when the semaphore signal operation it defines is executed on the device - The
stageMask
member of any element of thepSignalSemaphoreInfos
member of any element ofpSubmits
must only include pipeline stages that are supported by the queue family whichqueue
belongs to - The
stageMask
member of any element of thepWaitSemaphoreInfos
member of any element ofpSubmits
must only include pipeline stages that are supported by the queue family whichqueue
belongs to - When a semaphore wait
operation for a binary semaphore is executed, as defined by the
semaphore
member of any element of thepWaitSemaphoreInfos
member of any element ofpSubmits
, there must be no other queues waiting on the same semaphore - The
semaphore
member of any element of thepWaitSemaphoreInfos
member of any element ofpSubmits
must be semaphores that are signaled, or have semaphore signal operations previously submitted for execution - Any
semaphore
member of any element of thepWaitSemaphoreInfos
member of any element ofpSubmits
that was created with aSemaphoreTypeKHR
ofSEMAPHORE_TYPE_BINARY_KHR
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 - The
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
must be in the pending or executable state - If a command recorded
into the
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
was not recorded with theCOMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT
, it must not be in the pending state - Any
secondary command buffers recorded
into the
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
must be in the pending or executable state - If any
secondary command buffers recorded
into the
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
was not recorded with theCOMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT
, it must not be in the pending state - The
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
must have been allocated from aCommandPool
that was created for the same queue familyqueue
belongs to - If a command recorded
into the
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
includes a Queue Family Transfer Acquire Operation, there must exist a previously submitted Queue Family Transfer Release Operation on a queue in the queue family identified by the acquire operation, with parameters matching the acquire operation as defined in the definition of such acquire operations, and which happens before the acquire operation - If a command recorded
into the
commandBuffer
member of any element of thepCommandBufferInfos
member of any element ofpSubmits
was acmdBeginQuery
whosequeryPool
was created with aqueryType
ofQUERY_TYPE_PERFORMANCE_QUERY_KHR
, the profiling lock must have been held continuously on theDevice
thatqueue
was retrieved from, throughout recording of those command buffers - If
queue
was not created withDEVICE_QUEUE_CREATE_PROTECTED_BIT
, theflags
member of any element ofpSubmits
must not includeSUBMIT_PROTECTED_BIT_KHR
Valid Usage (Implicit)
-
queue
must be a validQueue
handle
- If
submitCount
is not0
,pSubmits
must be a valid pointer to an array ofsubmitCount
validSubmitInfo2KHR
structures - If
fence
is notNULL_HANDLE
,fence
must be a validFence
handle - Both of
fence
, andqueue
that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the sameDevice
Host Synchronization
- Host access to
queue
must be externally synchronized
- Host access to
fence
must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
- | - | Any |
Return Codes
See Also
cmdWriteTimestamp2KHR Source #
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> PipelineStageFlags2KHR |
|
-> QueryPool |
|
-> ("query" ::: Word32) |
|
-> io () |
vkCmdWriteTimestamp2KHR - Write a device timestamp into a query object
Description
When cmdWriteTimestamp2KHR
is submitted to a queue, it defines an
execution dependency on commands that were submitted before it, and
writes a timestamp to a query pool.
The first
synchronization scope
includes all commands that occur earlier in
submission order.
The synchronization scope is limited to operations on the pipeline stage
specified by stage
.
The second synchronization scope includes only the timestamp write operation.
When the timestamp value is written, the availability status of the query is set to available.
Note
If an implementation is unable to detect completion and latch the timer at any specific stage of the pipeline, it may instead do so at any logically later stage.
Comparisons between timestamps are not meaningful if the timestamps are written by commands submitted to different queues.
Note
An example of such a comparison is subtracting an older timestamp from a newer one to determine the execution time of a sequence of commands.
If cmdWriteTimestamp2KHR
is called while executing a render pass
instance that has multiview enabled, the timestamp uses N consecutive
query indices in the query pool (starting at query
) where N is the
number of bits set in the view mask of the subpass the command is
executed in. The resulting query values are determined by an
implementation-dependent choice of one of the following behaviors:
- The first query is a timestamp value and (if more than one bit is set in the view mask) zero is written to the remaining queries. If two timestamps are written in the same subpass, the sum of the execution time of all views between those commands is the difference between the first query written by each command.
- All N queries are timestamp values. If two timestamps are written in the same subpass, the sum of the execution time of all views between those commands is the sum of the difference between corresponding queries written by each command. The difference between corresponding queries may be the execution time of a single view.
In either case, the application can sum the differences between all N queries to determine the total execution time.
Valid Usage
- If the
geometry shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- The synchronization2 feature must be enabled
-
stage
must only include a single pipeline stage -
stage
must only include stages valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from -
queryPool
must have been created with aqueryType
ofQUERY_TYPE_TIMESTAMP
- The query identified
by
queryPool
andquery
must be unavailable - The command
pool’s queue family must support a non-zero
timestampValidBits
-
query
must be less than the number of queries inqueryPool
- All queries used by the command must be unavailable
- If
cmdWriteTimestamp2KHR
is called within a render pass instance, the sum ofquery
and the number of bits set in the current subpass’s view mask must be less than or equal to the number of queries inqueryPool
Valid Usage (Implicit)
-
commandBuffer
must be a validCommandBuffer
handle
-
stage
must be a valid combination ofPipelineStageFlagBits2KHR
values -
stage
must not be0
-
queryPool
must be a validQueryPool
handle -
commandBuffer
must be in the recording state - The
CommandPool
thatcommandBuffer
was allocated from must support transfer, graphics, or compute operations - Both of
commandBuffer
, andqueryPool
must have been created, allocated, or retrieved from the sameDevice
Host Synchronization
- Host access to
commandBuffer
must be externally synchronized
- Host access to the
CommandPool
thatcommandBuffer
was allocated from must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
Primary Secondary | Both | Transfer Graphics Compute |
See Also
VK_KHR_synchronization2,
CommandBuffer
, PipelineStageFlags2KHR
,
QueryPool
cmdWriteBufferMarker2AMD Source #
:: forall io. MonadIO io | |
=> CommandBuffer |
|
-> PipelineStageFlags2KHR |
|
-> ("dstBuffer" ::: Buffer) |
|
-> ("dstOffset" ::: DeviceSize) |
|
-> ("marker" ::: Word32) |
|
-> io () |
vkCmdWriteBufferMarker2AMD - Execute a pipelined write of a marker value into a buffer
Description
The command will write the 32-bit marker value into the buffer only
after all preceding commands have finished executing up to at least the
specified pipeline stage. This includes the completion of other
preceding cmdWriteBufferMarker2AMD
commands so long as their specified
pipeline stages occur either at the same time or earlier than this
command’s specified stage
.
While consecutive buffer marker writes with the same stage
parameter
implicitly complete in submission order, memory and execution
dependencies between buffer marker writes and other operations must
still be explicitly ordered using synchronization commands. The access
scope for buffer marker writes falls under the
ACCESS_TRANSFER_WRITE_BIT
, and the
pipeline stages for identifying the synchronization scope must include
both stage
and
PIPELINE_STAGE_TRANSFER_BIT
.
Note
Similar to cmdWriteTimestamp2KHR
, if an implementation is unable to
write a marker at any specific pipeline stage, it may instead do so at
any logically later stage.
Note
Implementations may only support a limited number of pipelined marker write operations in flight at a given time. Thus an excessive number of marker write operations may degrade command execution performance.
Valid Usage
- If the
geometry shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
stage
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- The synchronization2 feature must be enabled
-
stage
must include only a single pipeline stage -
stage
must include only stages that are valid for the queue family that was used to create the command pool thatcommandBuffer
was allocated from -
dstOffset
must be less than or equal to the size ofdstBuffer
minus4
-
dstBuffer
must have been created with theBUFFER_USAGE_TRANSFER_DST_BIT
usage flag - If
dstBuffer
is non-sparse then it must be bound completely and contiguously to a singleDeviceMemory
object -
dstOffset
must be a multiple of4
Valid Usage (Implicit)
-
commandBuffer
must be a validCommandBuffer
handle
-
stage
must be a valid combination ofPipelineStageFlagBits2KHR
values -
stage
must not be0
-
dstBuffer
must be a validBuffer
handle -
commandBuffer
must be in the recording state - The
CommandPool
thatcommandBuffer
was allocated from must support transfer, graphics, or compute operations - Both of
commandBuffer
, anddstBuffer
must have been created, allocated, or retrieved from the sameDevice
Host Synchronization
- Host access to
commandBuffer
must be externally synchronized
- Host access to the
CommandPool
thatcommandBuffer
was allocated from must be externally synchronized
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types |
---|---|---|
Primary Secondary | Both | Transfer Graphics Compute |
See Also
VK_AMD_buffer_marker,
VK_KHR_synchronization2,
Buffer
, CommandBuffer
,
DeviceSize
, PipelineStageFlags2KHR
getQueueCheckpointData2NV Source #
:: forall io. MonadIO io | |
=> Queue |
|
-> io ("checkpointData" ::: Vector CheckpointData2NV) |
vkGetQueueCheckpointData2NV - Retrieve diagnostic checkpoint data
Description
If pCheckpointData
is NULL
, then the number of checkpoint markers
available is returned in pCheckpointDataCount
. Otherwise,
pCheckpointDataCount
must point to a variable set by the user to the
number of elements in the pCheckpointData
array, and on return the
variable is overwritten with the number of structures actually written
to pCheckpointData
.
If pCheckpointDataCount
is less than the number of checkpoint markers
available, at most pCheckpointDataCount
structures will be written.
Valid Usage
Valid Usage (Implicit)
-
queue
must be a validQueue
handle
-
pCheckpointDataCount
must be a valid pointer to auint32_t
value - If the
value referenced by
pCheckpointDataCount
is not0
, andpCheckpointData
is notNULL
,pCheckpointData
must be a valid pointer to an array ofpCheckpointDataCount
CheckpointData2NV
structures
See Also
VK_KHR_synchronization2,
VK_NV_device_diagnostic_checkpoints,
CheckpointData2NV
, Queue
data MemoryBarrier2KHR Source #
VkMemoryBarrier2KHR - Structure specifying a global memory barrier
Description
This structure defines a memory dependency affecting all device memory.
The first
synchronization scope
and
access scope
described by this structure include only operations and memory accesses
specified by srcStageMask
and srcAccessMask
.
The second
synchronization scope
and
access scope
described by this structure include only operations and memory accesses
specified by dstStageMask
and dstAccessMask
.
Valid Usage
- If the
geometry shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
srcAccessMask
includesACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INDEX_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR
,PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_UNIFORM_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_STORAGE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFER_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFER_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_CLEAR_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_HOST_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
srcAccessMask
includesACCESS_2_HOST_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
srcAccessMask
includesACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI
,srcStageMask
must includePIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
srcAccessMask
includesACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
rayQuery
is not enabled and
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,srcStageMask
must not include any of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages exceptPIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR
- If the
geometry shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
dstAccessMask
includesACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INDEX_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR
,PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_UNIFORM_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_STORAGE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFER_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFER_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_CLEAR_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_HOST_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
dstAccessMask
includesACCESS_2_HOST_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
dstAccessMask
includesACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI
,dstStageMask
must includePIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
dstAccessMask
includesACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
rayQuery
is not enabled and
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,dstStageMask
must not include any of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages exceptPIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_MEMORY_BARRIER_2_KHR
-
srcStageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
srcAccessMask
must be a valid combination ofAccessFlagBits2KHR
values -
dstStageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
dstAccessMask
must be a valid combination ofAccessFlagBits2KHR
values
See Also
VK_KHR_synchronization2,
AccessFlags2KHR
, DependencyInfoKHR
, PipelineStageFlags2KHR
,
StructureType
MemoryBarrier2KHR | |
|
Instances
data ImageMemoryBarrier2KHR (es :: [Type]) Source #
VkImageMemoryBarrier2KHR - Structure specifying an image memory barrier
Description
This structure defines a memory dependency limited to an image subresource range, and can define a queue family transfer operation and image layout transition for that subresource range.
The first
synchronization scope
and
access scope
described by this structure include only operations and memory accesses
specified by srcStageMask
and srcAccessMask
.
The second
synchronization scope
and
access scope
described by this structure include only operations and memory accesses
specified by dstStageMask
and dstAccessMask
.
Both
access scopes
are limited to only memory accesses to image
in the subresource range
defined by subresourceRange
.
If image
was created with
SHARING_MODE_EXCLUSIVE
, and
srcQueueFamilyIndex
is not equal to dstQueueFamilyIndex
, this memory
barrier defines a
queue family transfer operation.
When executed on a queue in the family identified by
srcQueueFamilyIndex
, this barrier defines a
queue family release operation
for the specified image subresource range, and the second
synchronization and access scopes do not synchronize operations on that
queue. When executed on a queue in the family identified by
dstQueueFamilyIndex
, this barrier defines a
queue family acquire operation
for the specified image subresource range, and the first synchronization
and access scopes do not synchronize operations on that queue.
A
queue family transfer operation
is also defined if the values are not equal, and either is one of the
special queue family values reserved for external memory ownership
transfers, as described in
https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers.
A
queue family release operation
is defined when dstQueueFamilyIndex
is one of those values, and a
queue family acquire operation
is defined when srcQueueFamilyIndex
is one of those values.
If oldLayout
is not equal to newLayout
, then the memory barrier
defines an
image layout transition
for the specified image subresource range. If this memory barrier
defines a
queue family transfer operation,
the layout transition is only executed once between the queues.
Note
When the old and new layout are equal, the layout values are ignored - data is preserved no matter what values are specified, or what layout the image is currently in.
If image
has a multi-planar format and the image is disjoint, then
including
IMAGE_ASPECT_COLOR_BIT
in the
aspectMask
member of subresourceRange
is equivalent to including
IMAGE_ASPECT_PLANE_0_BIT
,
IMAGE_ASPECT_PLANE_1_BIT
, and
(for three-plane formats only)
IMAGE_ASPECT_PLANE_2_BIT
.
Valid Usage
- If the
geometry shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
srcAccessMask
includesACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INDEX_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR
,PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_UNIFORM_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_STORAGE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFER_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFER_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_CLEAR_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_HOST_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
srcAccessMask
includesACCESS_2_HOST_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
srcAccessMask
includesACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI
,srcStageMask
must includePIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
srcAccessMask
includesACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
rayQuery
is not enabled and
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,srcStageMask
must not include any of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages exceptPIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR
- If the
geometry shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
dstAccessMask
includesACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INDEX_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR
,PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_UNIFORM_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_STORAGE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFER_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFER_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_CLEAR_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_HOST_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
dstAccessMask
includesACCESS_2_HOST_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
dstAccessMask
includesACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI
,dstStageMask
must includePIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
dstAccessMask
includesACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
rayQuery
is not enabled and
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,dstStageMask
must not include any of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages exceptPIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR
-
subresourceRange.baseMipLevel
must be less than themipLevels
specified inImageCreateInfo
whenimage
was created - If
subresourceRange.levelCount
is notREMAINING_MIP_LEVELS
,subresourceRange.baseMipLevel
+subresourceRange.levelCount
must be less than or equal to themipLevels
specified inImageCreateInfo
whenimage
was created -
subresourceRange.baseArrayLayer
must be less than thearrayLayers
specified inImageCreateInfo
whenimage
was created - If
subresourceRange.layerCount
is notREMAINING_ARRAY_LAYERS
,subresourceRange.baseArrayLayer
+subresourceRange.layerCount
must be less than or equal to thearrayLayers
specified inImageCreateInfo
whenimage
was created - If
image
is non-sparse then it must be bound completely and contiguously to a singleDeviceMemory
object - If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_COLOR_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_SAMPLED_BIT
orIMAGE_USAGE_INPUT_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_TRANSFER_SRC_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_TRANSFER_DST_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_TRANSFER_DST_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition,oldLayout
must beIMAGE_LAYOUT_UNDEFINED
or the current layout of the image subresources affected by the barrier - If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition,newLayout
must not beIMAGE_LAYOUT_UNDEFINED
orIMAGE_LAYOUT_PREINITIALIZED
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL
thenimage
must have been created with at least one ofIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
,IMAGE_USAGE_SAMPLED_BIT
, orIMAGE_USAGE_INPUT_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
set - If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
thenimage
must have been created with at least one ofIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
,IMAGE_USAGE_SAMPLED_BIT
, orIMAGE_USAGE_INPUT_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL
thenimage
must have been created withIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
set - If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_ATTACHMENT_OPTIMAL_KHR
,image
must have been created withIMAGE_USAGE_COLOR_ATTACHMENT_BIT
orIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR
,image
must have been created with at least one ofIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
,IMAGE_USAGE_SAMPLED_BIT
, orIMAGE_USAGE_INPUT_ATTACHMENT_BIT
- If
srcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition, andoldLayout
ornewLayout
isIMAGE_LAYOUT_FRAGMENT_SHADING_RATE_ATTACHMENT_OPTIMAL_KHR
thenimage
must have been created withIMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR
set - If
image
has a single-plane color format or is not disjoint, then theaspectMask
member ofsubresourceRange
must beIMAGE_ASPECT_COLOR_BIT
- If
image
has a multi-planar format and the image is disjoint, then theaspectMask
member ofsubresourceRange
must include either at least one ofIMAGE_ASPECT_PLANE_0_BIT
,IMAGE_ASPECT_PLANE_1_BIT
, andIMAGE_ASPECT_PLANE_2_BIT
; or must includeIMAGE_ASPECT_COLOR_BIT
- If
image
has a multi-planar format with only two planes, then theaspectMask
member ofsubresourceRange
must not includeIMAGE_ASPECT_PLANE_2_BIT
- If
image
has a depth/stencil format with both depth and stencil and the separateDepthStencilLayouts feature is enabled, then theaspectMask
member ofsubresourceRange
must include either or bothIMAGE_ASPECT_DEPTH_BIT
andIMAGE_ASPECT_STENCIL_BIT
- If
image
has a depth/stencil format with both depth and stencil and the separateDepthStencilLayouts feature is not enabled, then theaspectMask
member ofsubresourceRange
must include bothIMAGE_ASPECT_DEPTH_BIT
andIMAGE_ASPECT_STENCIL_BIT
- If
srcQueueFamilyIndex
is not equal todstQueueFamilyIndex
, at least one must not be a special queue family reserved for external memory ownership transfers, as described in ??? - If
image
was created with a sharing mode ofSHARING_MODE_CONCURRENT
,srcQueueFamilyIndex
anddstQueueFamilyIndex
are not equal, and one ofsrcQueueFamilyIndex
anddstQueueFamilyIndex
is one of the special queue family values reserved for external memory transfers, the other must beQUEUE_FAMILY_IGNORED
- If
image
was created with a sharing mode ofSHARING_MODE_EXCLUSIVE
, andsrcQueueFamilyIndex
anddstQueueFamilyIndex
are not equal,srcQueueFamilyIndex
anddstQueueFamilyIndex
must both be valid queue families, or one of the special queue family values reserved for external memory transfers, as described in ??? - If either
srcStageMask
ordstStageMask
includesPIPELINE_STAGE_2_HOST_BIT_KHR
,srcQueueFamilyIndex
anddstQueueFamilyIndex
must be equal - If
srcStageMask
includesPIPELINE_STAGE_2_HOST_BIT_KHR
, andsrcQueueFamilyIndex
anddstQueueFamilyIndex
define a queue family ownership transfer oroldLayout
andnewLayout
define an image layout transition,oldLayout
must be one ofIMAGE_LAYOUT_PREINITIALIZED
,IMAGE_LAYOUT_UNDEFINED
, orIMAGE_LAYOUT_GENERAL
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_IMAGE_MEMORY_BARRIER_2_KHR
-
pNext
must beNULL
or a pointer to a valid instance ofSampleLocationsInfoEXT
- The
sType
value of each struct in thepNext
chain must be unique -
srcStageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
srcAccessMask
must be a valid combination ofAccessFlagBits2KHR
values -
dstStageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
dstAccessMask
must be a valid combination ofAccessFlagBits2KHR
values -
oldLayout
must be a validImageLayout
value -
newLayout
must be a validImageLayout
value -
image
must be a validImage
handle -
subresourceRange
must be a validImageSubresourceRange
structure
See Also
VK_KHR_synchronization2,
AccessFlags2KHR
, DependencyInfoKHR
, Image
,
ImageLayout
,
ImageSubresourceRange
,
PipelineStageFlags2KHR
,
StructureType
ImageMemoryBarrier2KHR | |
|
Instances
data BufferMemoryBarrier2KHR Source #
VkBufferMemoryBarrier2KHR - Structure specifying a buffer memory barrier
Description
This structure defines a memory dependency limited to a range of a buffer, and can define a queue family transfer operation for that range.
The first
synchronization scope
and
access scope
described by this structure include only operations and memory accesses
specified by srcStageMask
and srcAccessMask
.
The second
synchronization scope
and
access scope
described by this structure include only operations and memory accesses
specified by dstStageMask
and dstAccessMask
.
Both
access scopes
are limited to only memory accesses to buffer
in the range defined by
offset
and size
.
If buffer
was created with
SHARING_MODE_EXCLUSIVE
, and
srcQueueFamilyIndex
is not equal to dstQueueFamilyIndex
, this memory
barrier defines a
queue family transfer operation.
When executed on a queue in the family identified by
srcQueueFamilyIndex
, this barrier defines a
queue family release operation
for the specified buffer range, and the second synchronization and
access scopes do not synchronize operations on that queue. When executed
on a queue in the family identified by dstQueueFamilyIndex
, this
barrier defines a
queue family acquire operation
for the specified buffer range, and the first synchronization and access
scopes do not synchronize operations on that queue.
A
queue family transfer operation
is also defined if the values are not equal, and either is one of the
special queue family values reserved for external memory ownership
transfers, as described in
https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers.
A
queue family release operation
is defined when dstQueueFamilyIndex
is one of those values, and a
queue family acquire operation
is defined when srcQueueFamilyIndex
is one of those values.
Valid Usage
- If the
geometry shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
srcStageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
srcAccessMask
includesACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INDEX_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR
,PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_UNIFORM_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_STORAGE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_SHADER_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFER_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFER_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_CLEAR_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_HOST_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
srcAccessMask
includesACCESS_2_HOST_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
srcAccessMask
includesACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI
,srcStageMask
must includePIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
srcAccessMask
includesACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV
,srcStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT
,srcStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR
,srcStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
rayQuery
is not enabled and
srcAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,srcStageMask
must not include any of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages exceptPIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR
- If the
geometry shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
dstStageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
dstAccessMask
includesACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INDEX_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR
,PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR
,PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_UNIFORM_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_STORAGE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_SHADER_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFER_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFER_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_COPY_BIT_KHR
,PIPELINE_STAGE_2_BLIT_BIT_KHR
,PIPELINE_STAGE_2_RESOLVE_BIT_KHR
,PIPELINE_STAGE_2_CLEAR_BIT_KHR
,PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR
,PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_HOST_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
dstAccessMask
includesACCESS_2_HOST_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_HOST_BIT_KHR
- If
dstAccessMask
includesACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR
,PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_SHADING_RATE_IMAGE_READ_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
,PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI
,dstStageMask
must includePIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If
dstAccessMask
includesACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV
,dstStageMask
must includePIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT
,dstStageMask
must includePIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR
PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR
, orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
,PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
, or one of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages - If
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR
,dstStageMask
must includePIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR
orPIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
- If
rayQuery
is not enabled and
dstAccessMask
includesACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR
,dstStageMask
must not include any of theVK_PIPELINE_STAGE_*_SHADER_BIT
stages exceptPIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR
-
offset
must be less than the size ofbuffer
- If
size
is not equal toWHOLE_SIZE
,size
must be greater than0
- If
size
is not equal toWHOLE_SIZE
,size
must be less than or equal to than the size ofbuffer
minusoffset
- If
buffer
is non-sparse then it must be bound completely and contiguously to a singleDeviceMemory
object - If
srcQueueFamilyIndex
is not equal todstQueueFamilyIndex
, at least one must not be a special queue family reserved for external memory ownership transfers, as described in ??? - If
buffer
was created with a sharing mode ofSHARING_MODE_CONCURRENT
,srcQueueFamilyIndex
anddstQueueFamilyIndex
are not equal, and one ofsrcQueueFamilyIndex
anddstQueueFamilyIndex
is one of the special queue family values reserved for external memory transfers, the other must beQUEUE_FAMILY_IGNORED
- If
buffer
was created with a sharing mode ofSHARING_MODE_EXCLUSIVE
, andsrcQueueFamilyIndex
anddstQueueFamilyIndex
are not equal,srcQueueFamilyIndex
anddstQueueFamilyIndex
must both be valid queue families, or one of the special queue family values reserved for external memory transfers, as described in ??? - If either
srcStageMask
ordstStageMask
includesPIPELINE_STAGE_2_HOST_BIT_KHR
,srcQueueFamilyIndex
anddstQueueFamilyIndex
must be equal
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_BUFFER_MEMORY_BARRIER_2_KHR
-
pNext
must beNULL
-
srcStageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
srcAccessMask
must be a valid combination ofAccessFlagBits2KHR
values -
dstStageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values -
dstAccessMask
must be a valid combination ofAccessFlagBits2KHR
values -
buffer
must be a validBuffer
handle
See Also
VK_KHR_synchronization2,
AccessFlags2KHR
, Buffer
, DependencyInfoKHR
,
DeviceSize
, PipelineStageFlags2KHR
,
StructureType
BufferMemoryBarrier2KHR | |
|
Instances
data DependencyInfoKHR Source #
VkDependencyInfoKHR - Structure specifying dependency information for a synchronization command
Description
This structure defines a set of memory dependencies, as well as queue family transfer operations and image layout transitions.
Each member of pMemoryBarriers
, pBufferMemoryBarriers
, and
pImageMemoryBarriers
defines a separate
memory dependency.
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_DEPENDENCY_INFO_KHR
-
pNext
must beNULL
-
dependencyFlags
must be a valid combination ofDependencyFlagBits
values - If
memoryBarrierCount
is not0
,pMemoryBarriers
must be a valid pointer to an array ofmemoryBarrierCount
validMemoryBarrier2KHR
structures - If
bufferMemoryBarrierCount
is not0
,pBufferMemoryBarriers
must be a valid pointer to an array ofbufferMemoryBarrierCount
validBufferMemoryBarrier2KHR
structures - If
imageMemoryBarrierCount
is not0
,pImageMemoryBarriers
must be a valid pointer to an array ofimageMemoryBarrierCount
validImageMemoryBarrier2KHR
structures
See Also
VK_KHR_synchronization2,
BufferMemoryBarrier2KHR
,
DependencyFlags
,
ImageMemoryBarrier2KHR
, MemoryBarrier2KHR
,
StructureType
,
cmdPipelineBarrier2KHR
, cmdSetEvent2KHR
, cmdWaitEvents2KHR
DependencyInfoKHR | |
|
Instances
Show DependencyInfoKHR Source # | |
Defined in Vulkan.Extensions.VK_KHR_synchronization2 showsPrec :: Int -> DependencyInfoKHR -> ShowS # show :: DependencyInfoKHR -> String # showList :: [DependencyInfoKHR] -> ShowS # | |
FromCStruct DependencyInfoKHR Source # | |
ToCStruct DependencyInfoKHR Source # | |
Defined in Vulkan.Extensions.VK_KHR_synchronization2 withCStruct :: DependencyInfoKHR -> (Ptr DependencyInfoKHR -> IO b) -> IO b Source # pokeCStruct :: Ptr DependencyInfoKHR -> DependencyInfoKHR -> IO b -> IO b Source # withZeroCStruct :: (Ptr DependencyInfoKHR -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr DependencyInfoKHR -> IO b -> IO b Source # cStructSize :: Int Source # | |
Zero DependencyInfoKHR Source # | |
Defined in Vulkan.Extensions.VK_KHR_synchronization2 |
data SemaphoreSubmitInfoKHR Source #
VkSemaphoreSubmitInfoKHR - Structure specifying a semaphore signal or wait operation
Description
Whether this structure defines a semaphore wait or signal operation is defined by how it is used.
Valid Usage
- If the
geometry shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR
- If the
tessellation shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR
orPIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR
- If the
conditional rendering
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT
- If the
fragment density map
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT
- If the
transform feedback
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT
- If the
mesh shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_MESH_SHADER_BIT_NV
- If the
task shaders
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_TASK_SHADER_BIT_NV
- If the
shading rate image
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_SHADING_RATE_IMAGE_BIT_NV
- If the
subpass shading
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI
- If the
invocation mask image
feature is not enabled,
stageMask
must not containPIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI
- If the
device
thatsemaphore
was created on is not a device group,deviceIndex
must be0
- If the
device
thatsemaphore
was created on is a device group,deviceIndex
must be a valid device index
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_SEMAPHORE_SUBMIT_INFO_KHR
-
pNext
must beNULL
-
semaphore
must be a validSemaphore
handle -
stageMask
must be a valid combination ofPipelineStageFlagBits2KHR
values
See Also
VK_KHR_synchronization2,
PipelineStageFlags2KHR
, Semaphore
,
StructureType
, SubmitInfo2KHR
SemaphoreSubmitInfoKHR | |
|
Instances
data CommandBufferSubmitInfoKHR Source #
VkCommandBufferSubmitInfoKHR - Structure specifying a command buffer submission
Valid Usage
-
commandBuffer
must not have been allocated withCOMMAND_BUFFER_LEVEL_SECONDARY
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_COMMAND_BUFFER_SUBMIT_INFO_KHR
-
pNext
must beNULL
-
commandBuffer
must be a validCommandBuffer
handle
See Also
VK_KHR_synchronization2,
CommandBuffer
,
StructureType
, SubmitInfo2KHR
CommandBufferSubmitInfoKHR | |
|
Instances
data SubmitInfo2KHR (es :: [Type]) Source #
VkSubmitInfo2KHR - Structure specifying a queue submit operation
Valid Usage
- If the same semaphore is
used as the
semaphore
member of both an element ofpSignalSemaphoreInfos
andpWaitSemaphoreInfos
, and that semaphore is a timeline semaphore, thevalue
member of thepSignalSemaphoreInfos
element must be greater than thevalue
member of thepWaitSemaphoreInfos
element
- If the
semaphore
member of any element ofpSignalSemaphoreInfos
is a timeline semaphore, thevalue
member of that element must have a value greater than the current value of the semaphore when the semaphore signal operation is executed - If the
semaphore
member of any element ofpSignalSemaphoreInfos
is a timeline semaphore, thevalue
member of that element must have a value which does not differ from the current value of the semaphore or the value of any outstanding semaphore wait or signal operation on that semaphore by more than maxTimelineSemaphoreValueDifference - If the
semaphore
member of any element ofpWaitSemaphoreInfos
is a timeline semaphore, thevalue
member of that element must have a value which does not differ from the current value of the semaphore or the value of any outstanding semaphore wait or signal operation on that semaphore by more than maxTimelineSemaphoreValueDifference - If
flags
includesSUBMIT_PROTECTED_BIT_KHR
, all elements ofpCommandBuffers
must be protected command buffers - If
flags
does not includeSUBMIT_PROTECTED_BIT_KHR
, each element ofpCommandBuffers
must not be a protected command buffer - If any
commandBuffer
member of an element ofpCommandBufferInfos
contains any resumed render pass instances, they must be suspended by a render pass instance earlier in submission order withinpCommandBufferInfos
- If any
commandBuffer
member of an element ofpCommandBufferInfos
contains any suspended render pass instances, they must be resumed by a render pass instance later in submission order withinpCommandBufferInfos
- If any
commandBuffer
member of an element ofpCommandBufferInfos
contains any suspended render pass instances, there must be no action or synchronization commands between that render pass instance and the render pass instance that resumes it - If any
commandBuffer
member of an element ofpCommandBufferInfos
contains any suspended render pass instances, there must be no render pass instances between that render pass instance and the render pass instance that resumes it - If the
variableSampleLocations
limit is not supported, and any
commandBuffer
member of an element ofpCommandBufferInfos
contains any suspended render pass instances, where a graphics pipeline has been bound, any pipelines bound in the render pass instance that resumes it, or any subsequent render pass instances that resume from that one and so on, must use the same sample locations
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_SUBMIT_INFO_2_KHR
- Each
pNext
member of any structure (including this one) in thepNext
chain must be eitherNULL
or a pointer to a valid instance ofPerformanceQuerySubmitInfoKHR
,Win32KeyedMutexAcquireReleaseInfoKHR
, orWin32KeyedMutexAcquireReleaseInfoNV
- The
sType
value of each struct in thepNext
chain must be unique -
flags
must be a valid combination ofSubmitFlagBitsKHR
values - If
waitSemaphoreInfoCount
is not0
,pWaitSemaphoreInfos
must be a valid pointer to an array ofwaitSemaphoreInfoCount
validSemaphoreSubmitInfoKHR
structures - If
commandBufferInfoCount
is not0
,pCommandBufferInfos
must be a valid pointer to an array ofcommandBufferInfoCount
validCommandBufferSubmitInfoKHR
structures - If
signalSemaphoreInfoCount
is not0
,pSignalSemaphoreInfos
must be a valid pointer to an array ofsignalSemaphoreInfoCount
validSemaphoreSubmitInfoKHR
structures
See Also
VK_KHR_synchronization2,
CommandBufferSubmitInfoKHR
, SemaphoreSubmitInfoKHR
,
StructureType
, SubmitFlagsKHR
,
queueSubmit2KHR
SubmitInfo2KHR | |
|
Instances
data QueueFamilyCheckpointProperties2NV Source #
VkQueueFamilyCheckpointProperties2NV - Return structure for queue family checkpoint information query
Description
Additional queue family information can be queried by setting
QueueFamilyProperties2
::pNext
to point to a QueueFamilyCheckpointProperties2NV
structure.
Valid Usage (Implicit)
See Also
VK_KHR_synchronization2,
VK_NV_device_diagnostic_checkpoints,
PipelineStageFlags2KHR
,
StructureType
QueueFamilyCheckpointProperties2NV | |
|
Instances
data CheckpointData2NV Source #
VkCheckpointData2NV - Return structure for command buffer checkpoint data
Valid Usage (Implicit)
The stages at which a checkpoint marker can be executed are
implementation-defined and can be queried by calling
getPhysicalDeviceQueueFamilyProperties2
.
See Also
VK_KHR_synchronization2,
VK_NV_device_diagnostic_checkpoints,
PipelineStageFlags2KHR
,
StructureType
,
getQueueCheckpointData2NV
CheckpointData2NV | |
|
Instances
data PhysicalDeviceSynchronization2FeaturesKHR Source #
VkPhysicalDeviceSynchronization2FeaturesKHR - Structure describing whether the implementation supports v2 synchronization commands
Members
This structure describes the following feature:
Description
If the PhysicalDeviceSynchronization2FeaturesKHR
structure is included
in the pNext
chain of the
PhysicalDeviceFeatures2
structure passed to
getPhysicalDeviceFeatures2
,
it is filled in to indicate whether each corresponding feature is
supported. PhysicalDeviceSynchronization2FeaturesKHR
can also be
used in the pNext
chain of DeviceCreateInfo
to
selectively enable these features.
Valid Usage (Implicit)
See Also
Instances
type AccessFlags2KHR = AccessFlagBits2KHR Source #
newtype AccessFlagBits2KHR Source #
VkAccessFlagBits2KHR - Access flags for VkAccessFlags2KHR
Description
Note
In situations where an application wishes to select all access types for
a given set of pipeline stages, ACCESS_2_MEMORY_READ_BIT_KHR
or
ACCESS_2_MEMORY_WRITE_BIT_KHR
can be used. This is particularly useful
when specifying stages that only have a single access type.
Note
The AccessFlags2KHR
bitmask goes beyond the 31 individual bit flags
allowable within a C99 enum, which is how
AccessFlagBits
is defined. The
first 31 values are common to both, and are interchangeable.
See Also
Instances
newtype PipelineStageFlagBits2KHR Source #
VkPipelineStageFlagBits2KHR - Pipeline stage flags for VkPipelineStageFlags2KHR
Description
Note
The TOP
and BOTTOM
pipeline stages are deprecated, and applications
should prefer PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR
and
PIPELINE_STAGE_2_NONE_KHR
.
Note
The PipelineStageFlags2KHR
bitmask goes beyond the 31 individual bit
flags allowable within a C99 enum, which is how
PipelineStageFlagBits
is
defined. The first 31 values are common to both, and are
interchangeable.
See Also
Instances
type SubmitFlagsKHR = SubmitFlagBitsKHR Source #
newtype SubmitFlagBitsKHR Source #
VkSubmitFlagBitsKHR - Bitmask specifying behavior of a submission
See Also
pattern SUBMIT_PROTECTED_BIT_KHR :: SubmitFlagBitsKHR |
|
Instances
type KHR_SYNCHRONIZATION_2_SPEC_VERSION = 1 Source #
pattern KHR_SYNCHRONIZATION_2_SPEC_VERSION :: forall a. Integral a => a Source #
type KHR_SYNCHRONIZATION_2_EXTENSION_NAME = "VK_KHR_synchronization2" Source #
pattern KHR_SYNCHRONIZATION_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #
type Flags64 = Word64 Source #
VkFlags64 - Vulkan 64-bit bitmasks
Description
When the 31 bits available in Flags
are insufficient, the Flags64
type can be passed to commands and structures to represent up to 64
options. Flags64
is not used directly in the API. Instead, a
Vk*Flags2
type which is an alias of Flags64
, and whose name matches
the corresponding Vk*FlagBits2
that are valid for that type, is used.
Any Vk*Flags2
member or parameter used in the API as an input must
be a valid combination of bit flags. A valid combination is either zero
or the bitwise OR of valid bit flags. A bit flag is valid if:
- The bit flag is defined as part of the
Vk*FlagBits2
type, where the bits type is obtained by taking the flag type and replacing the trailingFlags2
withFlagBits2
. For example, a flag value of typeAccessFlags2KHR
must contain only bit flags defined byAccessFlagBits2KHR
. - The flag is allowed in the context in which it is being used. For example, in some cases, certain bit flags or combinations of bit flags are mutually exclusive.
Any Vk*Flags2
member or parameter returned from a query command or
otherwise output from Vulkan to the application may contain bit flags
undefined in its corresponding Vk*FlagBits2
type. An application
cannot rely on the state of these unspecified bits.
Note
Both the Vk*FlagBits2
type, and the individual bits defined for that
type, are defined as uint64_t
integers in the C API. This is in
contrast to the 32-bit types, where the Vk*FlagBits
type is defined as
a C enum
and the individual bits as enumerants belonging to that
enum
. As a result, there is less compile-time type checking possible
for the 64-bit types. This is unavoidable since there is no sufficiently
portable way to define a 64-bit enum
type in C99.