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

Vulkan.Core10.Queue

Synopsis

Documentation

getDeviceQueue Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the queue.

-> ("queueFamilyIndex" ::: Word32)

queueFamilyIndex is the index of the queue family to which the queue belongs.

-> ("queueIndex" ::: Word32)

queueIndex is the index within this queue family of the queue to retrieve.

-> io Queue 

vkGetDeviceQueue - Get a queue handle from a device

Description

getDeviceQueue must only be used to get queues that were created with the flags parameter of DeviceQueueCreateInfo set to zero. To get queues that were created with a non-zero flags parameter use getDeviceQueue2.

Valid Usage

  • queueFamilyIndex must be one of the queue family indices specified when device was created, via the DeviceQueueCreateInfo structure
  • queueIndex must be less than the number of queues created for the specified queue family index when device was created, via the queueCount member of the DeviceQueueCreateInfo structure
  • DeviceQueueCreateInfo::flags must have been set to zero when device was created

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pQueue must be a valid pointer to a Queue handle

See Also

Device, Queue

queueSubmit Source #

Arguments

:: forall io. MonadIO io 
=> Queue

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

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

pSubmits is a pointer to an array of SubmitInfo 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 () 

vkQueueSubmit - Submits a sequence of semaphores or command buffers to a queue

Description

queueSubmit is a queue submission command, with each batch defined by an element of pSubmits. Batches begin execution in the order they appear in pSubmits, but may complete out of order.

Fence and semaphore operations submitted with queueSubmit 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 and fence sections of the synchronization chapter.

Details on the interaction of pWaitDstStageMask with synchronization are described in the semaphore wait operation section of the synchronization chapter.

The order that batches appear in pSubmits is used to determine submission order, and thus all the implicit ordering guarantees that respect it. Other than these implicit ordering guarantees and any explicit synchronization primitives, these batches may overlap or otherwise execute out of order.

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 to the invalid state.

If queueSubmit 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 queueSubmit 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
  • Any calls to cmdSetEvent, cmdResetEvent or cmdWaitEvents that have been recorded into any of the command buffer elements of the pCommandBuffers member of any element of pSubmits, must not reference any Event that is referenced by any of those commands in a command buffer that has been submitted to another queue and is still in the pending state
  • Any stage flag included in any element of the pWaitDstStageMask member of any element of pSubmits must be a pipeline stage supported by one of the capabilities of queue, as specified in the table of supported pipeline stages
  • Each element of the pSignalSemaphores member of any element of pSubmits must be unsignaled when the semaphore signal operation it defines is executed on the device
  • When a semaphore wait operation referring to a binary semaphore defined by any element of the pWaitSemaphores member of any element of pSubmits executes on queue, there must be no other queues waiting on the same semaphore
  • All elements of the pWaitSemaphores member of all elements of pSubmits created with a SemaphoreType of SEMAPHORE_TYPE_BINARY must reference a semaphore signal operation that has been submitted for execution and any semaphore signal operations on which it depends (if any) must have also been submitted for execution
  • Each element of the pCommandBuffers member of each element of pSubmits must be in the pending or executable state
  • If any element of the pCommandBuffers 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 any element of the pCommandBuffers member of any element of pSubmits must be in the pending or executable state
  • If any secondary command buffers recorded into any element of the pCommandBuffers 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
  • Each element of the pCommandBuffers member of each element of pSubmits must have been allocated from a CommandPool that was created for the same queue family queue belongs to
  • If any element of pSubmits->pCommandBuffers 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 any element of pCommandBuffers 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
  • Any resource created with SHARING_MODE_EXCLUSIVE that is read by an operation specified by pSubmits must not be owned by any queue family other than the one which queue belongs to, at the time it is executed

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 SubmitInfo 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 Levels Render Pass Scope Supported Queue Types Pipeline Type
- - Any -

Return Codes

Success
Failure

See Also

Fence, Queue, SubmitInfo

queueWaitIdle Source #

Arguments

:: forall io. MonadIO io 
=> Queue

queue is the queue on which to wait.

-> io () 

vkQueueWaitIdle - Wait for a queue to become idle

Description

queueWaitIdle is equivalent to submitting a fence to a queue and waiting with an infinite timeout for that fence to signal.

Valid Usage (Implicit)

  • queue must be a valid Queue handle

Host Synchronization

  • Host access to queue must be externally synchronized

Command Properties

'

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

Return Codes

Success
Failure

See Also

Queue

queueWaitIdleSafe Source #

Arguments

:: forall io. MonadIO io 
=> Queue

queue is the queue on which to wait.

-> io () 

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

deviceWaitIdle Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device to idle.

-> io () 

vkDeviceWaitIdle - Wait for a device to become idle

Description

deviceWaitIdle is equivalent to calling queueWaitIdle for all queues owned by device.

Valid Usage (Implicit)

  • device must be a valid Device handle

Host Synchronization

  • Host access to all Queue objects created from device must be externally synchronized

Return Codes

Success
Failure

See Also

Device

deviceWaitIdleSafe Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device to idle.

-> io () 

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

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

VkSubmitInfo - Structure specifying a queue submit operation

Description

The order that command buffers appear in pCommandBuffers is used to determine submission order, and thus all the implicit ordering guarantees that respect it. Other than these implicit ordering guarantees and any explicit synchronization primitives, these command buffers may overlap or otherwise execute out of order.

Valid Usage

Valid Usage (Implicit)

See Also

CommandBuffer, PipelineStageFlags, Semaphore, StructureType, queueSubmit

Constructors

SubmitInfo 

Fields

Instances

Instances details
Extensible SubmitInfo Source # 
Instance details

Defined in Vulkan.Core10.Queue

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Queue

Methods

showsPrec :: Int -> SubmitInfo es -> ShowS #

show :: SubmitInfo es -> String #

showList :: [SubmitInfo es] -> ShowS #

Generic (SubmitInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Queue

Associated Types

type Rep (SubmitInfo es) :: Type -> Type #

Methods

from :: SubmitInfo es -> Rep (SubmitInfo es) x #

to :: Rep (SubmitInfo es) x -> SubmitInfo es #

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

Defined in Vulkan.Core10.Queue

Methods

peekCStruct :: Ptr (SubmitInfo es) -> IO (SubmitInfo es) Source #

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

Defined in Vulkan.Core10.Queue

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

Defined in Vulkan.Core10.Queue

Methods

zero :: SubmitInfo es Source #

type Rep (SubmitInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Queue

newtype PipelineStageFlagBits Source #

VkPipelineStageFlagBits - Bitmask specifying pipeline stages

See Also

CheckpointDataNV, PipelineStageFlags, cmdWriteBufferMarkerAMD, cmdWriteTimestamp

Bundled Patterns

pattern PIPELINE_STAGE_TOP_OF_PIPE_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_TOP_OF_PIPE_BIT is equivalent to PIPELINE_STAGE_ALL_COMMANDS_BIT with AccessFlags set to 0 when specified in the second synchronization scope, but specifies no stages in the first scope.

pattern PIPELINE_STAGE_DRAW_INDIRECT_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_DRAW_INDIRECT_BIT specifies the stage of the pipeline where Draw/DispatchIndirect data structures are consumed. This stage also includes reading commands written by cmdExecuteGeneratedCommandsNV.

pattern PIPELINE_STAGE_VERTEX_INPUT_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_VERTEX_INPUT_BIT specifies the stage of the pipeline where vertex and index buffers are consumed.

pattern PIPELINE_STAGE_VERTEX_SHADER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_VERTEX_SHADER_BIT specifies the vertex shader stage.

pattern PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT specifies the tessellation control shader stage.

pattern PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT specifies the tessellation evaluation shader stage.

pattern PIPELINE_STAGE_GEOMETRY_SHADER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_GEOMETRY_SHADER_BIT specifies the geometry shader stage.

pattern PIPELINE_STAGE_FRAGMENT_SHADER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_FRAGMENT_SHADER_BIT specifies the fragment shader stage.

pattern PIPELINE_STAGE_EARLY_FRAGMENT_TESTS_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_EARLY_FRAGMENT_TESTS_BIT 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_LATE_FRAGMENT_TESTS_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_LATE_FRAGMENT_TESTS_BIT 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_COLOR_ATTACHMENT_OUTPUT_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT 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_COMPUTE_SHADER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_COMPUTE_SHADER_BIT specifies the execution of a compute shader.

pattern PIPELINE_STAGE_TRANSFER_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_TRANSFER_BIT specifies the following commands:

pattern PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT is equivalent to PIPELINE_STAGE_ALL_COMMANDS_BIT with AccessFlags set to 0 when specified in the first synchronization scope, but specifies no stages in the second scope.

pattern PIPELINE_STAGE_HOST_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_HOST_BIT 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_ALL_GRAPHICS_BIT :: PipelineStageFlagBits

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

pattern PIPELINE_STAGE_ALL_COMMANDS_BIT :: PipelineStageFlagBits

PIPELINE_STAGE_ALL_COMMANDS_BIT specifies all commands supported on the queue it is used with.

pattern PIPELINE_STAGE_COMMAND_PREPROCESS_BIT_NV :: PipelineStageFlagBits

PIPELINE_STAGE_COMMAND_PREPROCESS_BIT_NV specifies the stage of the pipeline where device-side preprocessing for generated commands via cmdPreprocessGeneratedCommandsNV is handled.

pattern PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT :: PipelineStageFlagBits

PIPELINE_STAGE_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_MESH_SHADER_BIT_NV :: PipelineStageFlagBits

PIPELINE_STAGE_MESH_SHADER_BIT_NV specifies the mesh shader stage.

pattern PIPELINE_STAGE_TASK_SHADER_BIT_NV :: PipelineStageFlagBits

PIPELINE_STAGE_TASK_SHADER_BIT_NV specifies the task shader stage.

pattern PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV :: PipelineStageFlagBits

PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV specifies the stage of the pipeline where the shading rate image is read to determine the shading rate for portions of a rasterized primitive.

pattern PIPELINE_STAGE_ACCELERATION_STRUCTURE_BUILD_BIT_KHR :: PipelineStageFlagBits

PIPELINE_STAGE_ACCELERATION_STRUCTURE_BUILD_BIT_KHR specifies the execution of acceleration structure commands.

pattern PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR :: PipelineStageFlagBits

PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR specifies the execution of the ray tracing shader stages.

pattern PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT :: PipelineStageFlagBits

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

pattern PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT :: PipelineStageFlagBits

PIPELINE_STAGE_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 PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits

Ord PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits

Read PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits

Show PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits

Storable PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits

Bits PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits

Zero PipelineStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineStageFlagBits