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

Vulkan.Extensions.VK_KHR_synchronization2

Description

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
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 to newLayout.

  • 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 or PipelineStageFlagBits parameter have had those APIs replaced with equivalents using PipelineStageFlags2KHR.
  • 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 and PIPELINE_STAGE_2_NONE_KHR values.
  • MemoryBarrier2KHR can be chained to SubpassDependency2, overriding the original 32-bit stage and access masks.

New Commands

If VK_AMD_buffer_marker is supported:

If VK_NV_device_diagnostic_checkpoints is supported:

New Structures

If VK_NV_device_diagnostic_checkpoints is supported:

New Enums

New Bitmasks

New Enum Constants

If VK_EXT_blend_operation_advanced is supported:

If VK_EXT_conditional_rendering is supported:

If VK_EXT_fragment_density_map is supported:

If VK_EXT_transform_feedback is supported:

If VK_KHR_acceleration_structure is supported:

If VK_KHR_fragment_shading_rate is supported:

If VK_KHR_ray_tracing_pipeline is supported:

If VK_NV_device_diagnostic_checkpoints is supported:

If VK_NV_device_generated_commands is supported:

If VK_NV_mesh_shader is supported:

If VK_NV_ray_tracing is supported:

If VK_NV_shading_rate_image is supported:

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, 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

Documentation

cmdSetEvent2KHR Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> Event

event is the event that will be signaled.

-> DependencyInfoKHR

pDependencyInfo is a pointer to a DependencyInfoKHR structure defining the first scopes of this operation.

-> 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 dependencyFlags member of pDependencyInfo must be 0
  • The current device mask of commandBuffer must include exactly one physical device
  • The srcStageMask member of any element of the pMemoryBarriers, pBufferMemoryBarriers, or pImageMemoryBarriers members of pDependencyInfo must only include pipeline stages valid for the queue family that was used to create the command pool that commandBuffer was allocated from
  • The dstStageMask member of any element of the pMemoryBarriers, pBufferMemoryBarriers, or pImageMemoryBarriers members of pDependencyInfo must only include pipeline stages valid for the queue family that was used to create the command pool that commandBuffer was allocated from

Valid Usage (Implicit)

  • event must be a valid Event handle
  • pDependencyInfo must be a valid pointer to a valid DependencyInfoKHR structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • This command must only be called outside of a render pass instance
  • Both of commandBuffer, and event must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
Primary SecondaryOutside Graphics Compute

See Also

VK_KHR_synchronization2, CommandBuffer, DependencyInfoKHR, Event

cmdResetEvent2KHR Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> Event

event is the event that will be unsignaled.

-> ("stageMask" ::: PipelineStageFlags2KHR)

stageMask is a PipelineStageFlags2KHR mask of pipeline stages used to determine the first synchronization scope.

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

Valid Usage (Implicit)

  • event must be a valid Event handle
  • stageMask must be a valid combination of PipelineStageFlagBits2KHR values
  • stageMask must not be 0
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • This command must only be called outside of a render pass instance
  • Both of commandBuffer, and event must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
Primary SecondaryOutside Graphics Compute

See Also

VK_KHR_synchronization2, CommandBuffer, Event, PipelineStageFlags2KHR

cmdWaitEvents2KHR Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> ("events" ::: Vector Event)

pEvents is a pointer to an array of eventCount events to wait on.

-> ("dependencyInfos" ::: Vector DependencyInfoKHR)

pDependencyInfos is a pointer to an array of eventCount DependencyInfoKHR structures, defining the second synchronization scope.

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

  • Members of pEvents must not have been signaled by cmdSetEvent
  • For any element i of pEvents, if that event is signaled by cmdSetEvent2KHR, that command’s dependencyInfo parameter must be exactly equal to the ith element of pDependencyInfos
  • For any element i of pEvents, if that event is signaled by setEvent, barriers in the ith element of pDependencyInfos must include only host operations in their first synchronization scope
  • For any element i of pEvents, if barriers in the ith element of pDependencyInfos include only host operations, the ith element of pEvents must be signaled before cmdWaitEvents2KHR is executed
  • For any element i of pEvents, if barriers in the ith element of pDependencyInfos do not include host operations, the ith element of pEvents must be signaled by a corresponding cmdSetEvent2KHR that occurred earlier in submission order
  • The srcStageMask member of any element of the pMemoryBarriers, pBufferMemoryBarriers, or pImageMemoryBarriers members of pDependencyInfos must either include only pipeline stages valid for the queue family that was used to create the command pool that commandBuffer was allocated from, or include only PIPELINE_STAGE_2_HOST_BIT_KHR
  • The dstStageMask member of any element of the pMemoryBarriers, pBufferMemoryBarriers, or pImageMemoryBarriers members of pDependencyInfos must only include pipeline stages valid for the queue family that was used to create the command pool that commandBuffer was allocated from
  • The dependencyFlags member of any element of pDependencyInfo must be 0
  • If pEvents includes one or more events that will be signaled by setEvent after commandBuffer has been submitted to a queue, then cmdWaitEvents2KHR must not be called inside a render pass instance
  • commandBuffer’s current device mask must include exactly one physical device

Valid Usage (Implicit)

  • pEvents must be a valid pointer to an array of eventCount valid Event handles
  • pDependencyInfos must be a valid pointer to an array of eventCount valid DependencyInfoKHR structures
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • eventCount must be greater than 0
  • Both of commandBuffer, and the elements of pEvents must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
Primary SecondaryBoth Graphics Compute

See Also

VK_KHR_synchronization2, CommandBuffer, DependencyInfoKHR, Event

cmdWaitEvents2KHRSafe Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> ("events" ::: Vector Event)

pEvents is a pointer to an array of eventCount events to wait on.

-> ("dependencyInfos" ::: Vector DependencyInfoKHR)

pDependencyInfos is a pointer to an array of eventCount DependencyInfoKHR structures, defining the second synchronization scope.

-> io () 

A variant of cmdWaitEvents2KHR which makes a *safe* FFI call

cmdPipelineBarrier2KHR Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command is recorded.

-> DependencyInfoKHR

pDependencyInfo is a pointer to a DependencyInfoKHR structure defining the scopes of this operation.

-> 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, it must not include any buffer memory barriers
  • If cmdPipelineBarrier2KHR is called within a render pass instance, the image 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, the oldLayout and newLayout members of any image memory barrier included in this command must be equal
  • If cmdPipelineBarrier2KHR is called within a render pass instance, the srcQueueFamilyIndex and dstQueueFamilyIndex 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
  • The synchronization2 feature must be enabled
  • The srcStageMask member of any element of the pMemoryBarriers, pBufferMemoryBarriers, or pImageMemoryBarriers members of pDependencyInfo must only include pipeline stages valid for the queue family that was used to create the command pool that commandBuffer was allocated from
  • The dstStageMask member of any element of the pMemoryBarriers, pBufferMemoryBarriers, or pImageMemoryBarriers members of pDependencyInfo must only include pipeline stages valid for the queue family that was used to create the command pool that commandBuffer was allocated from

Valid Usage (Implicit)

  • pDependencyInfo must be a valid pointer to a valid DependencyInfoKHR structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer 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 that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
Primary Secondary Both Transfer Graphics Compute

See Also

VK_KHR_synchronization2, CommandBuffer, DependencyInfoKHR

queueSubmit2KHR Source #

Arguments

:: forall io. MonadIO io 
=> Queue

queue is the queue that the command buffers will be submitted to.

-> ("submits" ::: Vector (SomeStruct SubmitInfo2KHR))

pSubmits is a pointer to an array of SubmitInfo2KHR structures, each specifying a command buffer submission batch.

-> Fence

fence is an optional handle to a fence to be signaled once all submitted command buffers have completed execution. If fence is not NULL_HANDLE, it defines a fence signal operation.

-> io () 

vkQueueSubmit2KHR - Submits command buffers to a queue

Description

queueSubmit2KHR is a queue submission command, with each batch defined by an element of pSubmits as an instance of the SubmitInfo2KHR structure.

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 not NULL_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 the pCommandBufferInfos member of any element of pSubmits referenced an Event, 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 the pSignalSemaphoreInfos member of any element of pSubmits must be unsignaled when the semaphore signal operation it defines is executed on the device
  • The stageMask member of any element of the pSignalSemaphoreInfos member of any element of pSubmits must only include pipeline stages that are supported by the queue family which queue belongs to
  • The stageMask member of any element of the pWaitSemaphoreInfos member of any element of pSubmits must only include pipeline stages that are supported by the queue family which queue belongs to
  • When a semaphore wait operation for a binary semaphore is executed, as defined by the semaphore member of any element of the pWaitSemaphoreInfos member of any element of pSubmits, there must be no other queues waiting on the same semaphore
  • The semaphore member of any element of the pWaitSemaphoreInfos member of any element of pSubmits must be semaphores that are signaled, or have semaphore signal operations previously submitted for execution
  • Any semaphore member of any element of the pWaitSemaphoreInfos member of any element of pSubmits that was created with a SemaphoreTypeKHR of SEMAPHORE_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 the pCommandBufferInfos member of any element of pSubmits must be in the pending or executable state
  • If a command recorded into the commandBuffer member of any element of the pCommandBufferInfos member of any element of pSubmits was not recorded with the COMMAND_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 the pCommandBufferInfos member of any element of pSubmits must be in the pending or executable state
  • If any secondary command buffers recorded into the commandBuffer member of any element of the pCommandBufferInfos member of any element of pSubmits was not recorded with the COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT, it must not be in the pending state
  • The commandBuffer member of any element of the pCommandBufferInfos member of any element of pSubmits must have been allocated from a CommandPool that was created for the same queue family queue belongs to
  • If a command recorded into the commandBuffer member of any element of the pCommandBufferInfos member of any element of pSubmits 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 the pCommandBufferInfos member of any element of pSubmits was a cmdBeginQuery whose queryPool was created with a queryType of QUERY_TYPE_PERFORMANCE_QUERY_KHR, the profiling lock must have been held continuously on the Device that queue was retrieved from, throughout recording of those command buffers

Valid Usage (Implicit)

  • queue must be a valid Queue handle
  • If submitCount is not 0, pSubmits must be a valid pointer to an array of submitCount valid SubmitInfo2KHR structures
  • If fence is not NULL_HANDLE, fence must be a valid Fence handle
  • Both of fence, and queue that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to queue must be externally synchronized
  • Host access to fence must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
--Any

Return Codes

Success
Failure

See Also

VK_KHR_synchronization2, Fence, Queue, SubmitInfo2KHR

cmdWriteTimestamp2KHR Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> PipelineStageFlags2KHR

stage specifies a stage of the pipeline.

-> QueryPool

queryPool is the query pool that will manage the timestamp.

-> ("query" ::: Word32)

query is the query within the query pool that will contain the timestamp.

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

Valid Usage (Implicit)

  • stage must be a valid combination of PipelineStageFlagBits2KHR values
  • stage must not be 0
  • queryPool must be a valid QueryPool handle
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support transfer, graphics, or compute operations
  • Both of commandBuffer, and queryPool must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
Primary Secondary Both Transfer Graphics Compute

See Also

VK_KHR_synchronization2, CommandBuffer, PipelineStageFlags2KHR, QueryPool

cmdWriteBufferMarker2AMD Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> PipelineStageFlags2KHR

stage specifies the pipeline stage whose completion triggers the marker write.

-> ("dstBuffer" ::: Buffer)

dstBuffer is the buffer where the marker will be written.

-> ("dstOffset" ::: DeviceSize)

dstOffset is the byte offset into the buffer where the marker will be written.

-> ("marker" ::: Word32)

marker is the 32-bit value of the marker.

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

Valid Usage (Implicit)

  • stage must be a valid combination of PipelineStageFlagBits2KHR values
  • stage must not be 0
  • dstBuffer must be a valid Buffer handle
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support transfer, graphics, or compute operations
  • Both of commandBuffer, and dstBuffer must have been created, allocated, or retrieved from the same Device

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
Primary Secondary Both Transfer Graphics Compute

See Also

VK_AMD_buffer_marker, VK_KHR_synchronization2, Buffer, CommandBuffer, DeviceSize, PipelineStageFlags2KHR

getQueueCheckpointData2NV Source #

Arguments

:: forall io. MonadIO io 
=> Queue

queue is the Queue object the caller would like to retrieve checkpoint data for

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

  • The device that queue belongs to must be in the lost state

Valid Usage (Implicit)

  • queue must be a valid Queue handle
  • pCheckpointDataCount must be a valid pointer to a uint32_t value
  • If the value referenced by pCheckpointDataCount is not 0, and pCheckpointData is not NULL, pCheckpointData must be a valid pointer to an array of pCheckpointDataCount 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

Valid Usage (Implicit)

See Also

VK_KHR_synchronization2, AccessFlags2KHR, DependencyInfoKHR, PipelineStageFlags2KHR, StructureType

Constructors

MemoryBarrier2KHR 

Fields

Instances

Instances details
Eq MemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show MemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable MemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct MemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct MemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero MemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Valid Usage (Implicit)

See Also

VK_KHR_synchronization2, AccessFlags2KHR, DependencyInfoKHR, Image, ImageLayout, ImageSubresourceRange, PipelineStageFlags2KHR, StructureType

Constructors

ImageMemoryBarrier2KHR 

Fields

Instances

Instances details
Extensible ImageMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Methods

extensibleTypeName :: String Source #

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

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

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

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Valid Usage (Implicit)

See Also

VK_KHR_synchronization2, AccessFlags2KHR, Buffer, DependencyInfoKHR, DeviceSize, PipelineStageFlags2KHR, StructureType

Constructors

BufferMemoryBarrier2KHR 

Fields

Instances

Instances details
Eq BufferMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show BufferMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable BufferMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct BufferMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct BufferMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero BufferMemoryBarrier2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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)

  • pNext must be NULL
  • dependencyFlags must be a valid combination of DependencyFlagBits values
  • If memoryBarrierCount is not 0, pMemoryBarriers must be a valid pointer to an array of memoryBarrierCount valid MemoryBarrier2KHR structures
  • If bufferMemoryBarrierCount is not 0, pBufferMemoryBarriers must be a valid pointer to an array of bufferMemoryBarrierCount valid BufferMemoryBarrier2KHR structures
  • If imageMemoryBarrierCount is not 0, pImageMemoryBarriers must be a valid pointer to an array of imageMemoryBarrierCount valid ImageMemoryBarrier2KHR structures

See Also

VK_KHR_synchronization2, BufferMemoryBarrier2KHR, DependencyFlags, ImageMemoryBarrier2KHR, MemoryBarrier2KHR, StructureType, cmdPipelineBarrier2KHR, cmdSetEvent2KHR, cmdWaitEvents2KHR

Constructors

DependencyInfoKHR 

Fields

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

Valid Usage (Implicit)

See Also

VK_KHR_synchronization2, PipelineStageFlags2KHR, Semaphore, StructureType, SubmitInfo2KHR

Constructors

SemaphoreSubmitInfoKHR 

Fields

Instances

Instances details
Eq SemaphoreSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show SemaphoreSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable SemaphoreSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct SemaphoreSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct SemaphoreSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero SemaphoreSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

data CommandBufferSubmitInfoKHR Source #

VkCommandBufferSubmitInfoKHR - Structure specifying a command buffer submission

Valid Usage

  • If deviceMask is not 0, it must be a valid device mask

Valid Usage (Implicit)

  • pNext must be NULL
  • commandBuffer must be a valid CommandBuffer handle

See Also

VK_KHR_synchronization2, CommandBuffer, StructureType, SubmitInfo2KHR

Constructors

CommandBufferSubmitInfoKHR 

Fields

  • commandBuffer :: Ptr CommandBuffer_T

    commandBuffer is a CommandBuffer to be submitted for execution.

  • deviceMask :: Word32

    deviceMask is a bitmask indicating which devices in a device group execute the command buffer. A deviceMask of 0 is equivalent to setting all bits corresponding to valid devices in the group to 1.

Instances

Instances details
Eq CommandBufferSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show CommandBufferSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable CommandBufferSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct CommandBufferSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct CommandBufferSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero CommandBufferSubmitInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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 of pSignalSemaphoreInfos and pWaitSemaphoreInfos, and that semaphore is a timeline semaphore, the value member of the pSignalSemaphoreInfos element must be greater than the value member of the pWaitSemaphoreInfos element
  • If the semaphore member of any element of pSignalSemaphoreInfos is a timeline semaphore, the value 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 of pSignalSemaphoreInfos is a timeline semaphore, the value 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 of pWaitSemaphoreInfos is a timeline semaphore, the value 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 protected memory feature is not enabled, flags must not include SUBMIT_PROTECTED_BIT_KHR
  • If flags includes SUBMIT_PROTECTED_BIT_KHR, all elements of pCommandBuffers must be protected command buffers
  • If flags does not include SUBMIT_PROTECTED_BIT_KHR, each element of pCommandBuffers must not be a protected command buffer

Valid Usage (Implicit)

See Also

VK_KHR_synchronization2, CommandBufferSubmitInfoKHR, SemaphoreSubmitInfoKHR, StructureType, SubmitFlagsKHR, queueSubmit2KHR

Constructors

SubmitInfo2KHR 

Fields

Instances

Instances details
Extensible SubmitInfo2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Methods

extensibleTypeName :: String Source #

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

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

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

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Constructors

QueueFamilyCheckpointProperties2NV 

Fields

Instances

Instances details
Eq QueueFamilyCheckpointProperties2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show QueueFamilyCheckpointProperties2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable QueueFamilyCheckpointProperties2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct QueueFamilyCheckpointProperties2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct QueueFamilyCheckpointProperties2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero QueueFamilyCheckpointProperties2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

Constructors

CheckpointData2NV 

Fields

  • stage :: PipelineStageFlags2KHR

    stage indicates a single pipeline stage which the checkpoint marker data refers to.

  • checkpointMarker :: Ptr ()

    pCheckpointMarker contains the value of the last checkpoint marker executed in the stage that stage refers to.

Instances

Instances details
Show CheckpointData2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable CheckpointData2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct CheckpointData2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct CheckpointData2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero CheckpointData2NV Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

VK_KHR_synchronization2, Bool32, StructureType

Constructors

PhysicalDeviceSynchronization2FeaturesKHR 

Fields

  • synchronization2 :: Bool

    synchronization2 indicates whether the implementation supports the new set of synchronization commands introduced in VK_KHR_synchronization2.

Instances

Instances details
Eq PhysicalDeviceSynchronization2FeaturesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show PhysicalDeviceSynchronization2FeaturesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable PhysicalDeviceSynchronization2FeaturesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FromCStruct PhysicalDeviceSynchronization2FeaturesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

ToCStruct PhysicalDeviceSynchronization2FeaturesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero PhysicalDeviceSynchronization2FeaturesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

VK_KHR_synchronization2

Bundled Patterns

pattern ACCESS_2_NONE_KHR :: AccessFlagBits2KHR

ACCESS_2_NONE_KHR specifies no accesses.

pattern ACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_INDIRECT_COMMAND_READ_BIT_KHR specifies read access to command data read from indirect buffers as part of an indirect build, trace, drawing or dispatch command. Such access occurs in the PIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR pipeline stage.

pattern ACCESS_2_INDEX_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_INDEX_READ_BIT_KHR specifies read access to an index buffer as part of an indexed drawing command, bound by cmdBindIndexBuffer. Such access occurs in the PIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR pipeline stage.

pattern ACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_VERTEX_ATTRIBUTE_READ_BIT_KHR specifies read access to a vertex buffer as part of a drawing command, bound by cmdBindVertexBuffers. Such access occurs in the PIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR pipeline stage.

pattern ACCESS_2_UNIFORM_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_UNIFORM_READ_BIT_KHR specifies read access to a uniform buffer in any shader pipeline stage.

pattern ACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_INPUT_ATTACHMENT_READ_BIT_KHR specifies read access to an input attachment within a render pass during subpass shading or fragment shading. Such access occurs in the PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI or PIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR pipeline stage.

pattern ACCESS_2_SHADER_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_SHADER_READ_BIT_KHR specifies read access to a shader binding table in any shader pipeline. In addition, it is equivalent to the logical OR of:

  • VK_ACCESS_2_UNIFORM_READ_BIT_KHR
  • VK_ACCESS_2_SHADER_SAMPLED_READ_BIT_KHR
  • VK_ACCESS_2_SHADER_STORAGE_READ_BIT_KHR
pattern ACCESS_2_SHADER_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_SHADER_WRITE_BIT_KHR is equivalent to ACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR.

pattern ACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_COLOR_ATTACHMENT_READ_BIT_KHR specifies read access to a color attachment, such as via blending, logic operations, or via certain subpass load operations. It does not include advanced blend operations. Such access occurs in the PIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR pipeline stage.

pattern ACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_COLOR_ATTACHMENT_WRITE_BIT_KHR specifies write access to a color, resolve, or depth/stencil resolve attachment during a render pass or via certain subpass load and store operations. Such access occurs in the PIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR pipeline stage.

pattern ACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_DEPTH_STENCIL_ATTACHMENT_READ_BIT_KHR specifies read access to a depth/stencil attachment, via depth or stencil operations or via certain subpass load operations. Such access occurs in the PIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR or PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR pipeline stages.

pattern ACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT_KHR specifies write access to a depth/stencil attachment, via depth or stencil operations or via certain subpass load and store operations. Such access occurs in the PIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR or PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR pipeline stages.

pattern ACCESS_2_TRANSFER_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_TRANSFER_READ_BIT_KHR specifies read access to an image or buffer in a copy operation. Such access occurs in the PIPELINE_STAGE_2_COPY_BIT_KHR, PIPELINE_STAGE_2_BLIT_BIT_KHR, or PIPELINE_STAGE_2_RESOLVE_BIT_KHR pipeline stages.

pattern ACCESS_2_TRANSFER_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_TRANSFER_WRITE_BIT_KHR specifies write access to an image or buffer in a clear or copy operation. Such access occurs in the PIPELINE_STAGE_2_COPY_BIT_KHR, PIPELINE_STAGE_2_BLIT_BIT_KHR, PIPELINE_STAGE_2_CLEAR_BIT_KHR, or PIPELINE_STAGE_2_RESOLVE_BIT_KHR pipeline stages.

pattern ACCESS_2_HOST_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_HOST_READ_BIT_KHR specifies read access by a host operation. Accesses of this type are not performed through a resource, but directly on memory. Such access occurs in the PIPELINE_STAGE_2_HOST_BIT_KHR pipeline stage.

pattern ACCESS_2_HOST_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_HOST_WRITE_BIT_KHR specifies write access by a host operation. Accesses of this type are not performed through a resource, but directly on memory. Such access occurs in the PIPELINE_STAGE_2_HOST_BIT_KHR pipeline stage.

pattern ACCESS_2_MEMORY_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_MEMORY_READ_BIT_KHR specifies all read accesses. It is always valid in any access mask, and is treated as equivalent to setting all READ access flags that are valid where it is used.

pattern ACCESS_2_MEMORY_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_MEMORY_WRITE_BIT_KHR specifies all write accesses. It is always valid in any access mask, and is treated as equivalent to setting all WRITE access flags that are valid where it is used.

pattern ACCESS_2_SHADER_SAMPLED_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_SHADER_SAMPLED_READ_BIT_KHR specifies read access to a uniform texel buffer or sampled image in any shader pipeline stage.

pattern ACCESS_2_SHADER_STORAGE_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_SHADER_STORAGE_READ_BIT_KHR specifies read access to a storage buffer, physical storage buffer, storage texel buffer, or storage image in any shader pipeline stage.

pattern ACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_SHADER_STORAGE_WRITE_BIT_KHR specifies write access to a storage buffer, physical storage buffer, storage texel buffer, or storage image in any shader pipeline stage.

pattern ACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI :: AccessFlagBits2KHR

ACCESS_2_INVOCATION_MASK_READ_BIT_HUAWEI specifies read access to a invocation mask image in the PIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI pipeline stage.

pattern ACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT :: AccessFlagBits2KHR

ACCESS_2_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT specifies read access to color attachments, including advanced blend operations. Such access occurs in the PIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR pipeline stage.

pattern ACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT :: AccessFlagBits2KHR

ACCESS_2_FRAGMENT_DENSITY_MAP_READ_BIT_EXT specifies read access to a fragment density map attachment during dynamic fragment density map operations. Such access occurs in the PIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT pipeline stage.

pattern ACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_ACCELERATION_STRUCTURE_WRITE_BIT_KHR specifies write access to an acceleration structure or acceleration structure scratch buffer as part of a build or copy command. Such access occurs in the PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR pipeline stage.

pattern ACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_ACCELERATION_STRUCTURE_READ_BIT_KHR specifies read access to an acceleration structure as part of a trace, build, or copy command, or to an acceleration structure scratch buffer as part of a build command. Such access occurs in the PIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR pipeline stage or PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR pipeline stage.

pattern ACCESS_2_FRAGMENT_SHADING_RATE_ATTACHMENT_READ_BIT_KHR :: AccessFlagBits2KHR

ACCESS_2_FRAGMENT_SHADING_RATE_ATTACHMENT_READ_BIT_KHR specifies read access to a fragment shading rate attachment during rasterization. Such access occurs in the PIPELINE_STAGE_2_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR pipeline stage.

pattern ACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV :: AccessFlagBits2KHR

ACCESS_2_COMMAND_PREPROCESS_WRITE_BIT_NV specifies writes to the target command buffer preprocess outputs. Such access occurs in the PIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV pipeline stage.

pattern ACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV :: AccessFlagBits2KHR

ACCESS_2_COMMAND_PREPROCESS_READ_BIT_NV specifies reads from buffer inputs to cmdPreprocessGeneratedCommandsNV. Such access occurs in the PIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV pipeline stage.

pattern ACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT :: AccessFlagBits2KHR

ACCESS_2_CONDITIONAL_RENDERING_READ_BIT_EXT specifies read access to a predicate as part of conditional rendering. Such access occurs in the PIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT pipeline stage.

pattern ACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT :: AccessFlagBits2KHR

ACCESS_2_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT specifies write access to a transform feedback counter buffer which is written when cmdEndTransformFeedbackEXT executes. Such access occurs in the PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT pipeline stage.

pattern ACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT :: AccessFlagBits2KHR

ACCESS_2_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT specifies read access to a transform feedback counter buffer which is read when cmdBeginTransformFeedbackEXT executes. Such access occurs in the PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT pipeline stage.

pattern ACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT :: AccessFlagBits2KHR

ACCESS_2_TRANSFORM_FEEDBACK_WRITE_BIT_EXT specifies write access to a transform feedback buffer made when transform feedback is active. Such access occurs in the PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT pipeline stage.

Instances

Instances details
Eq AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Ord AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Read AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Bits AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FiniteBits AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero AccessFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

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

VK_KHR_synchronization2

Bundled Patterns

pattern PIPELINE_STAGE_2_NONE_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_NONE_KHR specifies no stages of execution.

pattern PIPELINE_STAGE_2_TOP_OF_PIPE_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_TOP_OF_PIPE_BIT_KHR is equivalent to PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR with AccessFlags2KHR set to 0 when specified in the second synchronization scope, but equivalent to PIPELINE_STAGE_2_NONE_KHR in the first scope.

pattern PIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_DRAW_INDIRECT_BIT_KHR specifies the stage of the pipeline where indirect command parameters are consumed. This stage also includes reading commands written by cmdPreprocessGeneratedCommandsNV.

pattern PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_VERTEX_INPUT_BIT_KHR is equivalent to the logical OR of:

pattern PIPELINE_STAGE_2_VERTEX_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_VERTEX_SHADER_BIT_KHR specifies the vertex shader stage.

pattern PIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_TESSELLATION_CONTROL_SHADER_BIT_KHR specifies the tessellation control shader stage.

pattern PIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_TESSELLATION_EVALUATION_SHADER_BIT_KHR specifies the tessellation evaluation shader stage.

pattern PIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_GEOMETRY_SHADER_BIT_KHR specifies the geometry shader stage.

pattern PIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_FRAGMENT_SHADER_BIT_KHR specifies the fragment shader stage.

pattern PIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_EARLY_FRAGMENT_TESTS_BIT_KHR specifies the stage of the pipeline where early fragment tests (depth and stencil tests before fragment shading) are performed. This stage also includes subpass load operations for framebuffer attachments with a depth/stencil format.

pattern PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_LATE_FRAGMENT_TESTS_BIT_KHR specifies the stage of the pipeline where late fragment tests (depth and stencil tests after fragment shading) are performed. This stage also includes subpass store operations for framebuffer attachments with a depth/stencil format.

pattern PIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_COLOR_ATTACHMENT_OUTPUT_BIT_KHR specifies the stage of the pipeline after blending where the final color values are output from the pipeline. This stage also includes subpass load and store operations and multisample resolve operations for framebuffer attachments with a color or depth/stencil format.

pattern PIPELINE_STAGE_2_COMPUTE_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_COMPUTE_SHADER_BIT_KHR specifies the compute shader stage.

pattern PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_ALL_TRANSFER_BIT_KHR is equivalent to specifying all of:

pattern PIPELINE_STAGE_2_BOTTOM_OF_PIPE_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_BOTTOM_OF_PIPE_BIT_KHR is equivalent to PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR with AccessFlags2KHR set to 0 when specified in the first synchronization scope, but equivalent to PIPELINE_STAGE_2_NONE_KHR in the second scope.

pattern PIPELINE_STAGE_2_HOST_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_HOST_BIT_KHR specifies a pseudo-stage indicating execution on the host of reads/writes of device memory. This stage is not invoked by any commands recorded in a command buffer.

pattern PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_ALL_GRAPHICS_BIT_KHR specifies the execution of all graphics pipeline stages, and is equivalent to the logical OR of:

pattern PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_ALL_COMMANDS_BIT_KHR specifies all operations performed by all commands supported on the queue it is used with.

pattern PIPELINE_STAGE_2_COPY_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_COPY_BIT_KHR specifies the execution of all copy commands, including cmdCopyQueryPoolResults.

pattern PIPELINE_STAGE_2_RESOLVE_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_RESOLVE_BIT_KHR specifies the execution of cmdResolveImage.

pattern PIPELINE_STAGE_2_BLIT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_BLIT_BIT_KHR specifies the execution of cmdBlitImage.

pattern PIPELINE_STAGE_2_CLEAR_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_CLEAR_BIT_KHR specifies the execution of clear commands, with the exception of cmdClearAttachments.

pattern PIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_INDEX_INPUT_BIT_KHR specifies the stage of the pipeline where index buffers are consumed.

pattern PIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_VERTEX_ATTRIBUTE_INPUT_BIT_KHR specifies the stage of the pipeline where vertex buffers are consumed.

pattern PIPELINE_STAGE_2_PRE_RASTERIZATION_SHADERS_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_PRE_RASTERIZATION_SHADERS_BIT_KHR is equivalent to specifying all supported pre-rasterization shader stages:

pattern PIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_INVOCATION_MASK_BIT_HUAWEI specifies the stage of the pipeline where the invocation mask image is read by the implementation to optimize the ray dispatch.

pattern PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_SUBPASS_SHADING_BIT_HUAWEI specifies the subpass shading shader stage.

pattern PIPELINE_STAGE_2_MESH_SHADER_BIT_NV :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_MESH_SHADER_BIT_NV specifies the mesh shader stage.

pattern PIPELINE_STAGE_2_TASK_SHADER_BIT_NV :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_TASK_SHADER_BIT_NV specifies the task shader stage.

pattern PIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_FRAGMENT_DENSITY_PROCESS_BIT_EXT specifies the stage of the pipeline where the fragment density map is read to generate the fragment areas.

pattern PIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_RAY_TRACING_SHADER_BIT_KHR specifies the execution of the ray tracing shader stages.

pattern PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_ACCELERATION_STRUCTURE_BUILD_BIT_KHR specifies the execution of acceleration structure commands.

pattern PIPELINE_STAGE_2_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR specifies the stage of the pipeline where the fragment shading rate attachment or shading rate image is read to determine the fragment shading rate for portions of a rasterized primitive.

pattern PIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_COMMAND_PREPROCESS_BIT_NV specifies the stage of the pipeline where device-side generation of commands via cmdPreprocessGeneratedCommandsNV is handled.

pattern PIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_CONDITIONAL_RENDERING_BIT_EXT specifies the stage of the pipeline where the predicate of conditional rendering is consumed.

pattern PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT :: PipelineStageFlagBits2KHR

PIPELINE_STAGE_2_TRANSFORM_FEEDBACK_BIT_EXT specifies the stage of the pipeline where vertex attribute output values are written to the transform feedback buffers.

Instances

Instances details
Eq PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Ord PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Read PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Bits PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Methods

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

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

xor :: PipelineStageFlagBits2KHR -> PipelineStageFlagBits2KHR -> PipelineStageFlagBits2KHR #

complement :: PipelineStageFlagBits2KHR -> PipelineStageFlagBits2KHR #

shift :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

rotate :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

zeroBits :: PipelineStageFlagBits2KHR #

bit :: Int -> PipelineStageFlagBits2KHR #

setBit :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

clearBit :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

complementBit :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

testBit :: PipelineStageFlagBits2KHR -> Int -> Bool #

bitSizeMaybe :: PipelineStageFlagBits2KHR -> Maybe Int #

bitSize :: PipelineStageFlagBits2KHR -> Int #

isSigned :: PipelineStageFlagBits2KHR -> Bool #

shiftL :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

unsafeShiftL :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

shiftR :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

unsafeShiftR :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

rotateL :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

rotateR :: PipelineStageFlagBits2KHR -> Int -> PipelineStageFlagBits2KHR #

popCount :: PipelineStageFlagBits2KHR -> Int #

FiniteBits PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero PipelineStageFlagBits2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

newtype SubmitFlagBitsKHR Source #

VkSubmitFlagBitsKHR - Bitmask specifying behavior of a submission

See Also

VK_KHR_synchronization2, SubmitFlagsKHR

Constructors

SubmitFlagBitsKHR Flags 

Bundled Patterns

pattern SUBMIT_PROTECTED_BIT_KHR :: SubmitFlagBitsKHR

SUBMIT_PROTECTED_BIT_KHR specifies that this batch is a protected submission.

Instances

Instances details
Eq SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Ord SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Read SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Show SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Storable SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Bits SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

FiniteBits SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

Zero SubmitFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_synchronization2

type KHR_SYNCHRONIZATION_2_EXTENSION_NAME = "VK_KHR_synchronization2" Source #

pattern KHR_SYNCHRONIZATION_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #