vulkan-3.24.4: Bindings to the Vulkan graphics API.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vulkan.Extensions.VK_EXT_conditional_rendering

Description

Name

VK_EXT_conditional_rendering - device extension

VK_EXT_conditional_rendering

Name String
VK_EXT_conditional_rendering
Extension Type
Device extension
Registered Extension Number
82
Revision
2
Extension and Version Dependencies
  • Requires support for Vulkan 1.0
Contact

Other Extension Metadata

Last Modified Date
2018-05-21
IP Status
No known IP claims.
Contributors
  • Vikram Kushwaha, NVIDIA
  • Daniel Rakos, AMD
  • Jesse Hall, Google
  • Jeff Bolz, NVIDIA
  • Piers Daniell, NVIDIA
  • Stuart Smith, Imagination Technologies

Description

This extension allows the execution of one or more rendering commands to be conditional on a value in buffer memory. This may help an application reduce the latency by conditionally discarding rendering commands without application intervention. The conditional rendering commands are limited to draws, compute dispatches and clearing attachments within a conditional rendering block.

New Commands

New Structures

New Enums

New Bitmasks

New Enum Constants

Issues

1) Should conditional rendering affect copy and blit commands?

RESOLVED: Conditional rendering should not affect copies and blits.

2) Should secondary command buffers be allowed to execute while conditional rendering is active in the primary command buffer?

RESOLVED: The rendering commands in secondary command buffer will be affected by an active conditional rendering in primary command buffer if the conditionalRenderingEnable is set to TRUE. Conditional rendering must not be active in the primary command buffer if conditionalRenderingEnable is FALSE.

Examples

None.

Version History

  • Revision 1, 2018-04-19 (Vikram Kushwaha)

    • First Version
  • Revision 2, 2018-05-21 (Vikram Kushwaha)

    • Add new pipeline stage, access flags and limit conditional rendering to a subpass or entire render pass.

See Also

CommandBufferInheritanceConditionalRenderingInfoEXT, ConditionalRenderingBeginInfoEXT, ConditionalRenderingFlagBitsEXT, ConditionalRenderingFlagsEXT, PhysicalDeviceConditionalRenderingFeaturesEXT, cmdBeginConditionalRenderingEXT, cmdEndConditionalRenderingEXT

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

cmdBeginConditionalRenderingEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

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

-> ConditionalRenderingBeginInfoEXT

pConditionalRenderingBegin is a pointer to a ConditionalRenderingBeginInfoEXT structure specifying parameters of conditional rendering.

-> io () 

vkCmdBeginConditionalRenderingEXT - Define the beginning of a conditional rendering block

Valid Usage

  • Conditional rendering must not already be active

Valid Usage (Implicit)

  • pConditionalRenderingBegin must be a valid pointer to a valid ConditionalRenderingBeginInfoEXT 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 video coding scope

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 ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryBoth Outside Graphics ComputeAction State

See Also

VK_EXT_conditional_rendering, CommandBuffer, ConditionalRenderingBeginInfoEXT

cmdUseConditionalRenderingEXT :: forall io r. MonadIO io => CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r Source #

This function will call the supplied action between calls to cmdBeginConditionalRenderingEXT and cmdEndConditionalRenderingEXT

Note that cmdEndConditionalRenderingEXT is *not* called if an exception is thrown by the inner action.

cmdEndConditionalRenderingEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

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

-> io () 

vkCmdEndConditionalRenderingEXT - Define the end of a conditional rendering block

Description

Once ended, conditional rendering becomes inactive.

Valid Usage

  • Conditional rendering must be active
  • If conditional rendering was made active outside of a render pass instance, it must not be ended inside a render pass instance
  • If conditional rendering was made active within a subpass it must be ended in the same subpass

Valid Usage (Implicit)

  • 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 video coding scope

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 ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryBoth Outside Graphics ComputeAction State

See Also

VK_EXT_conditional_rendering, CommandBuffer

data ConditionalRenderingBeginInfoEXT Source #

VkConditionalRenderingBeginInfoEXT - Structure specifying conditional rendering begin information

Description

If the 32-bit value at offset in buffer memory is zero, then the rendering commands are discarded, otherwise they are executed as normal. If the value of the predicate in buffer memory changes while conditional rendering is active, the rendering commands may be discarded in an implementation-dependent way. Some implementations may latch the value of the predicate upon beginning conditional rendering while others may read it before every rendering command.

Valid Usage

  • If buffer is non-sparse then it must be bound completely and contiguously to a single DeviceMemory object

Valid Usage (Implicit)

See Also

VK_EXT_conditional_rendering, Buffer, ConditionalRenderingFlagsEXT, DeviceSize, StructureType, cmdBeginConditionalRenderingEXT

Constructors

ConditionalRenderingBeginInfoEXT 

Fields

Instances

Instances details
Storable ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Show ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Eq ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

FromCStruct ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

ToCStruct ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Zero ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

data CommandBufferInheritanceConditionalRenderingInfoEXT Source #

VkCommandBufferInheritanceConditionalRenderingInfoEXT - Structure specifying command buffer inheritance information

Description

If this structure is not present, the behavior is as if conditionalRenderingEnable is FALSE.

Valid Usage

Valid Usage (Implicit)

See Also

VK_EXT_conditional_rendering, Bool32, StructureType

Constructors

CommandBufferInheritanceConditionalRenderingInfoEXT 

Fields

  • conditionalRenderingEnable :: Bool

    conditionalRenderingEnable specifies whether the command buffer can be executed while conditional rendering is active in the primary command buffer. If this is TRUE, then this command buffer can be executed whether the primary command buffer has active conditional rendering or not. If this is FALSE, then the primary command buffer must not have conditional rendering active.

Instances

Instances details
Storable CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Show CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Eq CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

FromCStruct CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

ToCStruct CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Zero CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

data PhysicalDeviceConditionalRenderingFeaturesEXT Source #

VkPhysicalDeviceConditionalRenderingFeaturesEXT - Structure describing if a secondary command buffer can be executed if conditional rendering is active in the primary command buffer

Members

This structure describes the following features:

Description

If the PhysicalDeviceConditionalRenderingFeaturesEXT 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. PhysicalDeviceConditionalRenderingFeaturesEXT can also be used in the pNext chain of DeviceCreateInfo to selectively enable these features.

Valid Usage (Implicit)

See Also

VK_EXT_conditional_rendering, Bool32, StructureType

Constructors

PhysicalDeviceConditionalRenderingFeaturesEXT 

Fields

  • conditionalRendering :: Bool

    conditionalRendering specifies whether conditional rendering is supported.

  • inheritedConditionalRendering :: Bool

    inheritedConditionalRendering specifies whether a secondary command buffer can be executed while conditional rendering is active in the primary command buffer.

Instances

Instances details
Storable PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Show PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Eq PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

FromCStruct PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

ToCStruct PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Zero PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

newtype ConditionalRenderingFlagBitsEXT Source #

VkConditionalRenderingFlagBitsEXT - Specify the behavior of conditional rendering

See Also

VK_EXT_conditional_rendering, ConditionalRenderingFlagsEXT

Bundled Patterns

pattern CONDITIONAL_RENDERING_INVERTED_BIT_EXT :: ConditionalRenderingFlagBitsEXT

CONDITIONAL_RENDERING_INVERTED_BIT_EXT specifies the condition used to determine whether to discard rendering commands or not. That is, if the 32-bit predicate read from buffer memory at offset is zero, the rendering commands are not discarded, and if non zero, then they are discarded.

Instances

Instances details
Storable ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Bits ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Methods

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

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

xor :: ConditionalRenderingFlagBitsEXT -> ConditionalRenderingFlagBitsEXT -> ConditionalRenderingFlagBitsEXT #

complement :: ConditionalRenderingFlagBitsEXT -> ConditionalRenderingFlagBitsEXT #

shift :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

rotate :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

zeroBits :: ConditionalRenderingFlagBitsEXT #

bit :: Int -> ConditionalRenderingFlagBitsEXT #

setBit :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

clearBit :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

complementBit :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

testBit :: ConditionalRenderingFlagBitsEXT -> Int -> Bool #

bitSizeMaybe :: ConditionalRenderingFlagBitsEXT -> Maybe Int #

bitSize :: ConditionalRenderingFlagBitsEXT -> Int #

isSigned :: ConditionalRenderingFlagBitsEXT -> Bool #

shiftL :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

unsafeShiftL :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

shiftR :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

unsafeShiftR :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

rotateL :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

rotateR :: ConditionalRenderingFlagBitsEXT -> Int -> ConditionalRenderingFlagBitsEXT #

popCount :: ConditionalRenderingFlagBitsEXT -> Int #

FiniteBits ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Read ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Show ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Eq ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Ord ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

Zero ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_conditional_rendering

type EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering" Source #