vulkan-3.1.0.0: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Synopsis

Documentation

cmdBeginConditionalRenderingEXT :: forall io. MonadIO io => CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io () Source #

vkCmdBeginConditionalRenderingEXT - Define the beginning of a conditional rendering block

Parameters

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

Valid Usage

  • Conditional rendering must not already be active

Valid Usage (Implicit)

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 Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics Compute

See Also

CommandBuffer, ConditionalRenderingBeginInfoEXT

cmdEndConditionalRenderingEXT :: forall io. MonadIO io => CommandBuffer -> io () Source #

vkCmdEndConditionalRenderingEXT - Define the end of a conditional rendering block

Parameters

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

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

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 Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics Compute

See Also

CommandBuffer

data ConditionalRenderingBeginInfoEXT Source #

VkConditionalRenderingBeginInfoEXT - Structure specifying conditional rendering begin info

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

Buffer, ConditionalRenderingFlagsEXT, DeviceSize, StructureType, cmdBeginConditionalRenderingEXT

Constructors

ConditionalRenderingBeginInfoEXT 

Fields

Instances
Show ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Storable ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

FromCStruct ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

ToCStruct ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Zero ConditionalRenderingBeginInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

data CommandBufferInheritanceConditionalRenderingInfoEXT Source #

VkCommandBufferInheritanceConditionalRenderingInfoEXT - Structure specifying command buffer inheritance info

Description

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

Valid Usage

Valid Usage (Implicit)

See Also

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
Show CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Storable CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

FromCStruct CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

ToCStruct CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Zero CommandBufferInheritanceConditionalRenderingInfoEXT Source # 
Instance details

Defined in Graphics.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

Description

If the PhysicalDeviceConditionalRenderingFeaturesEXT structure is included in the pNext chain of PhysicalDeviceFeatures2, it is filled with values indicating the implementation-dependent behavior. PhysicalDeviceConditionalRenderingFeaturesEXT can also be included in pNext chain of DeviceCreateInfo to enable the features.

Valid Usage (Implicit)

See Also

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
Show PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Storable PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

FromCStruct PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

ToCStruct PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Zero PhysicalDeviceConditionalRenderingFeaturesEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

newtype ConditionalRenderingFlagBitsEXT Source #

VkConditionalRenderingFlagBitsEXT - Specify the behavior of conditional rendering

See Also

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
Eq ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Ord ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Read ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Show ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Storable ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

Bits ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.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 #

Zero ConditionalRenderingFlagBitsEXT Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_EXT_conditional_rendering

type EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering" Source #