vulkan-2.0.0.1: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Extensions.VK_NVX_device_generated_commands

Synopsis

Documentation

newtype VkIndirectCommandsTokenTypeNVX Source #

VkIndirectCommandsTokenTypeNVX - Enum specifying

Description

'

Token type Equivalent command
VK_INDIRECT_COMMANDS_TOKEN_TYPE_PIPELINE_NVX vkCmdBindPipeline
VK_INDIRECT_COMMANDS_TOKEN_TYPE_DESCRIPTOR_SET_NVX vkCmdBindDescriptorSets
VK_INDIRECT_COMMANDS_TOKEN_TYPE_INDEX_BUFFER_NVX vkCmdBindIndexBuffer
VK_INDIRECT_COMMANDS_TOKEN_TYPE_VERTEX_BUFFER_NVX vkCmdBindVertexBuffers
VK_INDIRECT_COMMANDS_TOKEN_TYPE_PUSH_CONSTANT_NVX vkCmdPushConstants
VK_INDIRECT_COMMANDS_TOKEN_TYPE_DRAW_INDEXED_NVX vkCmdDrawIndexedIndirect
VK_INDIRECT_COMMANDS_TOKEN_TYPE_DRAW_NVX vkCmdDrawIndirect
VK_INDIRECT_COMMANDS_TOKEN_TYPE_DISPATCH_NVX vkCmdDispatchIndirect

Supported indirect command tokens

See Also

VkIndirectCommandsLayoutTokenNVX, VkIndirectCommandsTokenNVX

Instances
Eq VkIndirectCommandsTokenTypeNVX Source # 
Instance details
Ord VkIndirectCommandsTokenTypeNVX Source # 
Instance details
Read VkIndirectCommandsTokenTypeNVX Source # 
Instance details
Show VkIndirectCommandsTokenTypeNVX Source # 
Instance details
Storable VkIndirectCommandsTokenTypeNVX Source # 
Instance details

newtype VkObjectEntryTypeNVX Source #

Instances
Eq VkObjectEntryTypeNVX Source # 
Instance details
Ord VkObjectEntryTypeNVX Source # 
Instance details
Read VkObjectEntryTypeNVX Source # 
Instance details
Show VkObjectEntryTypeNVX Source # 
Instance details
Storable VkObjectEntryTypeNVX Source # 
Instance details

pattern VK_OBJECT_ENTRY_TYPE_DESCRIPTOR_SET_NVX :: VkObjectEntryTypeNVX Source #

VK_OBJECT_ENTRY_TYPE_DESCRIPTOR_SET_NVX specifies a VkDescriptorSet resource entry that is registered via VkObjectTableDescriptorSetEntryNVX.

pattern VK_OBJECT_ENTRY_TYPE_PIPELINE_NVX :: VkObjectEntryTypeNVX Source #

VK_OBJECT_ENTRY_TYPE_PIPELINE_NVX specifies a VkPipeline resource entry that is registered via VkObjectTablePipelineEntryNVX.

pattern VK_OBJECT_ENTRY_TYPE_INDEX_BUFFER_NVX :: VkObjectEntryTypeNVX Source #

VK_OBJECT_ENTRY_TYPE_INDEX_BUFFER_NVX specifies a VkBuffer resource entry that is registered via VkObjectTableIndexBufferEntryNVX.

pattern VK_OBJECT_ENTRY_TYPE_VERTEX_BUFFER_NVX :: VkObjectEntryTypeNVX Source #

VK_OBJECT_ENTRY_TYPE_VERTEX_BUFFER_NVX specifies a VkBuffer resource entry that is registered via VkObjectTableVertexBufferEntryNVX.

pattern VK_OBJECT_ENTRY_TYPE_PUSH_CONSTANT_NVX :: VkObjectEntryTypeNVX Source #

VK_OBJECT_ENTRY_TYPE_PUSH_CONSTANT_NVX specifies the resource entry is registered via VkObjectTablePushConstantEntryNVX.

newtype VkIndirectCommandsLayoutUsageFlagBitsNVX Source #

VkIndirectCommandsLayoutUsageFlagBitsNVX - Bitmask specifying allowed usage of a indirect commands layout

See Also

VkIndirectCommandsLayoutUsageFlagsNVX

Instances
Eq VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details
Ord VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details
Read VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details
Show VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details
Storable VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details
Bits VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details

Methods

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

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

xor :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> VkIndirectCommandsLayoutUsageFlagBitsNVX -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

complement :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

shift :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

rotate :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

zeroBits :: VkIndirectCommandsLayoutUsageFlagBitsNVX #

bit :: Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

setBit :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

clearBit :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

complementBit :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

testBit :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> Bool #

bitSizeMaybe :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Maybe Int #

bitSize :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int #

isSigned :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Bool #

shiftL :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

unsafeShiftL :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

shiftR :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

unsafeShiftR :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

rotateL :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

rotateR :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int -> VkIndirectCommandsLayoutUsageFlagBitsNVX #

popCount :: VkIndirectCommandsLayoutUsageFlagBitsNVX -> Int #

FiniteBits VkIndirectCommandsLayoutUsageFlagBitsNVX Source # 
Instance details

pattern VK_INDIRECT_COMMANDS_LAYOUT_USAGE_UNORDERED_SEQUENCES_BIT_NVX :: VkIndirectCommandsLayoutUsageFlagBitsNVX Source #

VK_INDIRECT_COMMANDS_LAYOUT_USAGE_UNORDERED_SEQUENCES_BIT_NVX specifies that the processing of sequences can happen at an implementation-dependent order, which is not guaranteed to be coherent across multiple invocations.

pattern VK_INDIRECT_COMMANDS_LAYOUT_USAGE_SPARSE_SEQUENCES_BIT_NVX :: VkIndirectCommandsLayoutUsageFlagBitsNVX Source #

VK_INDIRECT_COMMANDS_LAYOUT_USAGE_SPARSE_SEQUENCES_BIT_NVX specifies that there is likely a high difference between allocated number of sequences and actually used.

pattern VK_INDIRECT_COMMANDS_LAYOUT_USAGE_EMPTY_EXECUTIONS_BIT_NVX :: VkIndirectCommandsLayoutUsageFlagBitsNVX Source #

VK_INDIRECT_COMMANDS_LAYOUT_USAGE_EMPTY_EXECUTIONS_BIT_NVX specifies that there are likely many draw or dispatch calls that are zero-sized (zero grid dimension, no primitives to render).

pattern VK_INDIRECT_COMMANDS_LAYOUT_USAGE_INDEXED_SEQUENCES_BIT_NVX :: VkIndirectCommandsLayoutUsageFlagBitsNVX Source #

VK_INDIRECT_COMMANDS_LAYOUT_USAGE_INDEXED_SEQUENCES_BIT_NVX specifies that the input data for the sequences is not implicitly indexed from 0..sequencesUsed but a user provided VkBuffer encoding the index is provided.

newtype VkObjectEntryUsageFlagBitsNVX Source #

VkObjectEntryUsageFlagBitsNVX - Bitmask specifying allowed usage of an object entry

See Also

VkObjectEntryUsageFlagsNVX

Instances
Eq VkObjectEntryUsageFlagBitsNVX Source # 
Instance details
Ord VkObjectEntryUsageFlagBitsNVX Source # 
Instance details
Read VkObjectEntryUsageFlagBitsNVX Source # 
Instance details
Show VkObjectEntryUsageFlagBitsNVX Source # 
Instance details
Storable VkObjectEntryUsageFlagBitsNVX Source # 
Instance details
Bits VkObjectEntryUsageFlagBitsNVX Source # 
Instance details

Methods

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

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

xor :: VkObjectEntryUsageFlagBitsNVX -> VkObjectEntryUsageFlagBitsNVX -> VkObjectEntryUsageFlagBitsNVX #

complement :: VkObjectEntryUsageFlagBitsNVX -> VkObjectEntryUsageFlagBitsNVX #

shift :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

rotate :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

zeroBits :: VkObjectEntryUsageFlagBitsNVX #

bit :: Int -> VkObjectEntryUsageFlagBitsNVX #

setBit :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

clearBit :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

complementBit :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

testBit :: VkObjectEntryUsageFlagBitsNVX -> Int -> Bool #

bitSizeMaybe :: VkObjectEntryUsageFlagBitsNVX -> Maybe Int #

bitSize :: VkObjectEntryUsageFlagBitsNVX -> Int #

isSigned :: VkObjectEntryUsageFlagBitsNVX -> Bool #

shiftL :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

unsafeShiftL :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

shiftR :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

unsafeShiftR :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

rotateL :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

rotateR :: VkObjectEntryUsageFlagBitsNVX -> Int -> VkObjectEntryUsageFlagBitsNVX #

popCount :: VkObjectEntryUsageFlagBitsNVX -> Int #

FiniteBits VkObjectEntryUsageFlagBitsNVX Source # 
Instance details

pattern VK_OBJECT_ENTRY_USAGE_GRAPHICS_BIT_NVX :: VkObjectEntryUsageFlagBitsNVX Source #

VK_OBJECT_ENTRY_USAGE_GRAPHICS_BIT_NVX specifies that the resource is bound to VK_PIPELINE_BIND_POINT_GRAPHICS

pattern VK_OBJECT_ENTRY_USAGE_COMPUTE_BIT_NVX :: VkObjectEntryUsageFlagBitsNVX Source #

VK_OBJECT_ENTRY_USAGE_COMPUTE_BIT_NVX specifies that the resource is bound to VK_PIPELINE_BIND_POINT_COMPUTE

type VkIndirectCommandsLayoutNVX = Ptr VkIndirectCommandsLayoutNVX_T Source #

VkIndirectCommandsLayoutNVX - Opaque handle to an indirect commands layout object

See Also

VkCmdProcessCommandsInfoNVX, VkCmdReserveSpaceForCommandsInfoNVX, vkCreateIndirectCommandsLayoutNVX, vkDestroyIndirectCommandsLayoutNVX

vkCmdProcessCommandsNVX :: ("commandBuffer" ::: VkCommandBuffer) -> ("pProcessCommandsInfo" ::: Ptr VkCmdProcessCommandsInfoNVX) -> IO () Source #

vkCmdProcessCommandsNVX - Performs the generation of commands on the device

Parameters

  • commandBuffer is the primary command buffer in which the generation process takes space.
  • pProcessCommandsInfo is a pointer to an instance of the VkCmdProcessCommandsInfoNVX structure containing parameters affecting the processing of commands.

Valid Usage (Implicit)

  • commandBuffer must be a valid VkCommandBuffer handle
  • pProcessCommandsInfo must be a valid pointer to a valid VkCmdProcessCommandsInfoNVX structure
  • commandBuffer must be in the recording state
  • The VkCommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • This command must only be called inside of a render pass instance

Host Synchronization

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

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Inside Graphics Compute

See Also

VkCmdProcessCommandsInfoNVX, VkCommandBuffer

vkCmdReserveSpaceForCommandsNVX :: ("commandBuffer" ::: VkCommandBuffer) -> ("pReserveSpaceInfo" ::: Ptr VkCmdReserveSpaceForCommandsInfoNVX) -> IO () Source #

vkCmdReserveSpaceForCommandsNVX - Perform a reservation of command buffer space

Parameters

  • commandBuffer is the secondary command buffer in which the space for device-generated commands is reserved.
  • pProcessCommandsInfo is a pointer to an instance of the vkCmdReserveSpaceForCommandsNVX structure containing parameters affecting the reservation of command buffer space.

Valid Usage

  • The provided commandBuffer must not have had a prior space reservation since its creation or the last reset.
  • The state of the commandBuffer must be legal to execute all commands within the sequence provided by the indirectCommandsLayout member of pProcessCommandsInfo.

Valid Usage (Implicit)

  • commandBuffer must be a valid VkCommandBuffer handle
  • pReserveSpaceInfo must be a valid pointer to a valid VkCmdReserveSpaceForCommandsInfoNVX structure
  • commandBuffer must be in the recording state
  • The VkCommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • This command must only be called inside of a render pass instance
  • commandBuffer must be a secondary VkCommandBuffer

Host Synchronization

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

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Secondary Inside Graphics Compute

See Also

VkCmdReserveSpaceForCommandsInfoNVX, VkCommandBuffer

vkCreateIndirectCommandsLayoutNVX :: ("device" ::: VkDevice) -> ("pCreateInfo" ::: Ptr VkIndirectCommandsLayoutCreateInfoNVX) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> ("pIndirectCommandsLayout" ::: Ptr VkIndirectCommandsLayoutNVX) -> IO VkResult Source #

vkCreateIndirectCommandsLayoutNVX - Create an indirect command layout object

Parameters

  • device is the logical device that creates the indirect command layout.
  • pCreateInfo is a pointer to an instance of the VkIndirectCommandsLayoutCreateInfoNVX structure containing parameters affecting creation of the indirect command layout.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pIndirectCommandsLayout points to a VkIndirectCommandsLayoutNVX handle in which the resulting indirect command layout is returned.

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • pCreateInfo must be a valid pointer to a valid VkIndirectCommandsLayoutCreateInfoNVX structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • pIndirectCommandsLayout must be a valid pointer to a VkIndirectCommandsLayoutNVX handle

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY

See Also

VkAllocationCallbacks, VkDevice, VkIndirectCommandsLayoutCreateInfoNVX, VkIndirectCommandsLayoutNVX

vkDestroyIndirectCommandsLayoutNVX :: ("device" ::: VkDevice) -> ("indirectCommandsLayout" ::: VkIndirectCommandsLayoutNVX) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> IO () Source #

vkDestroyIndirectCommandsLayoutNVX - Destroy a object table

Parameters

  • device is the logical device that destroys the layout.
  • indirectCommandsLayout is the table to destroy.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.

Valid Usage

  • All submitted commands that refer to indirectCommandsLayout must have completed execution
  • If VkAllocationCallbacks were provided when objectTable was created, a compatible set of callbacks must be provided here
  • If no VkAllocationCallbacks were provided when objectTable was created, pAllocator must be NULL

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • indirectCommandsLayout must be a valid VkIndirectCommandsLayoutNVX handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • indirectCommandsLayout must have been created, allocated, or retrieved from device

See Also

VkAllocationCallbacks, VkDevice, VkIndirectCommandsLayoutNVX

vkCreateObjectTableNVX :: ("device" ::: VkDevice) -> ("pCreateInfo" ::: Ptr VkObjectTableCreateInfoNVX) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> ("pObjectTable" ::: Ptr VkObjectTableNVX) -> IO VkResult Source #

vkCreateObjectTableNVX - Create an object table

Parameters

  • device is the logical device that creates the object table.
  • pCreateInfo is a pointer to an instance of the VkObjectTableCreateInfoNVX structure containing parameters affecting creation of the table.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pObjectTable points to a VkObjectTableNVX handle in which the resulting object table is returned.

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • pCreateInfo must be a valid pointer to a valid VkObjectTableCreateInfoNVX structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • pObjectTable must be a valid pointer to a VkObjectTableNVX handle

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY

See Also

VkAllocationCallbacks, VkDevice, VkObjectTableCreateInfoNVX, VkObjectTableNVX

vkDestroyObjectTableNVX :: ("device" ::: VkDevice) -> ("objectTable" ::: VkObjectTableNVX) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> IO () Source #

vkDestroyObjectTableNVX - Destroy a object table

Parameters

  • device is the logical device that destroys the table.
  • objectTable is the table to destroy.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.

Valid Usage

  • All submitted commands that refer to objectTable must have completed execution.
  • If VkAllocationCallbacks were provided when objectTable was created, a compatible set of callbacks must be provided here.
  • If no VkAllocationCallbacks were provided when objectTable was created, pAllocator must be NULL.

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • objectTable must be a valid VkObjectTableNVX handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • objectTable must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to objectTable must be externally synchronized

See Also

VkAllocationCallbacks, VkDevice, VkObjectTableNVX

vkRegisterObjectsNVX :: ("device" ::: VkDevice) -> ("objectTable" ::: VkObjectTableNVX) -> ("objectCount" ::: Word32) -> ("ppObjectTableEntries" ::: Ptr (Ptr VkObjectTableEntryNVX)) -> ("pObjectIndices" ::: Ptr Word32) -> IO VkResult Source #

vkRegisterObjectsNVX - Register resource bindings in an object table

Parameters

  • device is the logical device that creates the object table.
  • objectTable is the table for which the resources are registered.
  • objectCount is the number of resources to register.
  • ppObjectTableEntries provides an array for detailed binding informations, each array element is a pointer to a struct of type VkObjectTablePipelineEntryNVX, VkObjectTableDescriptorSetEntryNVX, VkObjectTableVertexBufferEntryNVX, VkObjectTableIndexBufferEntryNVX or VkObjectTablePushConstantEntryNVX (see below for details).
  • pObjectIndices are the indices at which each resource is registered.

Valid Usage

  • The contents of pObjectTableEntry must yield plausible bindings supported by the device.
  • At any pObjectIndices there must not be a registered resource already.
  • Any value inside pObjectIndices must be below the appropriate VkObjectTableCreateInfoNVX::pObjectEntryCounts limits provided at objectTable creation time.

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • objectTable must be a valid VkObjectTableNVX handle
  • ppObjectTableEntries must be a valid pointer to an array of objectCount valid VkObjectTableEntryNVX structures
  • pObjectIndices must be a valid pointer to an array of objectCount uint32_t values
  • objectCount must be greater than 0
  • objectTable must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to objectTable must be externally synchronized

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY

See Also

VkDevice, VkObjectTableEntryNVX, VkObjectTableNVX

vkUnregisterObjectsNVX :: ("device" ::: VkDevice) -> ("objectTable" ::: VkObjectTableNVX) -> ("objectCount" ::: Word32) -> ("pObjectEntryTypes" ::: Ptr VkObjectEntryTypeNVX) -> ("pObjectIndices" ::: Ptr Word32) -> IO VkResult Source #

vkUnregisterObjectsNVX - Unregister resource bindings in an object table

Parameters

  • device is the logical device that creates the object table.
  • objectTable is the table from which the resources are unregistered.
  • objectCount is the number of resources being removed from the object table.
  • pObjectEntryType provides an array of VkObjectEntryTypeNVX for the resources being removed.
  • pObjectIndices provides the array of object indices to be removed.

Valid Usage

  • At any pObjectIndices there must be a registered resource already.
  • The pObjectEntryTypes of the resource at pObjectIndices must match.
  • All operations on the device using the registered resource must have been completed.

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • objectTable must be a valid VkObjectTableNVX handle
  • pObjectEntryTypes must be a valid pointer to an array of objectCount valid VkObjectEntryTypeNVX values
  • pObjectIndices must be a valid pointer to an array of objectCount uint32_t values
  • objectCount must be greater than 0
  • objectTable must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to objectTable must be externally synchronized

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY

See Also

VkDevice, VkObjectEntryTypeNVX, VkObjectTableNVX

vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX :: ("physicalDevice" ::: VkPhysicalDevice) -> ("pFeatures" ::: Ptr VkDeviceGeneratedCommandsFeaturesNVX) -> ("pLimits" ::: Ptr VkDeviceGeneratedCommandsLimitsNVX) -> IO () Source #

vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX - Returns device-generated commands related properties of a physical device

Parameters

  • physicalDevice is the handle to the physical device whose properties will be queried.

Valid Usage (Implicit)

  • physicalDevice must be a valid VkPhysicalDevice handle
  • pFeatures must be a valid pointer to a VkDeviceGeneratedCommandsFeaturesNVX structure
  • pLimits must be a valid pointer to a VkDeviceGeneratedCommandsLimitsNVX structure

See Also

VkDeviceGeneratedCommandsFeaturesNVX, VkDeviceGeneratedCommandsLimitsNVX, VkPhysicalDevice

data VkDeviceGeneratedCommandsFeaturesNVX Source #

VkDeviceGeneratedCommandsFeaturesNVX - Structure specifying physical device support

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_DEVICE_GENERATED_COMMANDS_FEATURES_NVX
  • pNext must be NULL

See Also

VkBool32, VkStructureType, vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX

Constructors

VkDeviceGeneratedCommandsFeaturesNVX 

Fields

  • vkSType :: VkStructureType

    sType is the type of this structure.

  • vkPNext :: Ptr ()

    pNext is NULL or a pointer to an extension-specific structure.

  • vkComputeBindingPointSupport :: VkBool32

    computeBindingPointSupport specifies whether the VkObjectTableNVX supports entries with VK_OBJECT_ENTRY_USAGE_GRAPHICS_BIT_NVX bit set and VkIndirectCommandsLayoutNVX supports VK_PIPELINE_BIND_POINT_COMPUTE.

data VkDeviceGeneratedCommandsLimitsNVX Source #

VkDeviceGeneratedCommandsLimitsNVX - Structure specifying physical device limits

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_DEVICE_GENERATED_COMMANDS_LIMITS_NVX
  • pNext must be NULL

See Also

VkStructureType, vkGetPhysicalDeviceGeneratedCommandsPropertiesNVX

Constructors

VkDeviceGeneratedCommandsLimitsNVX 

Fields

data VkIndirectCommandsTokenNVX Source #

VkIndirectCommandsTokenNVX - Structure specifying parameters for the reservation of command buffer space

Valid Usage

  • The buffer’s usage flag must have the VK_BUFFER_USAGE_INDIRECT_BUFFER_BIT bit set.
  • The offset must be aligned to VkDeviceGeneratedCommandsLimitsNVX::minCommandsTokenBufferOffsetAlignment.

Valid Usage (Implicit)

  • buffer must be a valid VkBuffer handle

See Also

VkBuffer, VkCmdProcessCommandsInfoNVX, VkDeviceSize, VkIndirectCommandsTokenTypeNVX

Constructors

VkIndirectCommandsTokenNVX 

Fields

data VkIndirectCommandsLayoutTokenNVX Source #

VkIndirectCommandsLayoutTokenNVX - Struct specifying the details of an indirect command layout token

Valid Usage

  • bindingUnit must stay within device supported limits for the appropriate commands.
  • dynamicCount must stay within device supported limits for the appropriate commands.
  • divisor must be greater than 0 and a power of two.

Valid Usage (Implicit)

See Also

VkIndirectCommandsLayoutCreateInfoNVX, VkIndirectCommandsTokenTypeNVX

Constructors

VkIndirectCommandsLayoutTokenNVX 

Fields

data VkIndirectCommandsLayoutCreateInfoNVX Source #

VkIndirectCommandsLayoutCreateInfoNVX - Structure specifying the parameters of a newly created indirect commands layout object

Description

The following code illustrates some of the key flags:

void cmdProcessAllSequences(cmd, objectTable, indirectCommandsLayout, pIndirectCommandsTokens, sequencesCount, indexbuffer, indexbufferoffset)
{
  for (s = 0; s < sequencesCount; s++)
  {
    sequence = s;

    if (indirectCommandsLayout.flags & VK_INDIRECT_COMMANDS_LAYOUT_USAGE_UNORDERED_SEQUENCES_BIT_NVX) {
      sequence = incoherent_implementation_dependent_permutation[ sequence ];
    }
    if (indirectCommandsLayout.flags & VK_INDIRECT_COMMANDS_LAYOUT_USAGE_INDEXED_SEQUENCES_BIT_NVX) {
      sequence = indexbuffer.load_uint32( sequence * sizeof(uint32_t) + indexbufferoffset);
    }

    cmdProcessSequence( cmd, objectTable, indirectCommandsLayout, pIndirectCommandsTokens, sequence );
  }
}

Valid Usage

  • tokenCount must be greater than 0 and below VkDeviceGeneratedCommandsLimitsNVX::maxIndirectCommandsLayoutTokenCount
  • If the VkDeviceGeneratedCommandsFeaturesNVX::computeBindingPointSupport feature is not enabled, then pipelineBindPoint must not be VK_PIPELINE_BIND_POINT_COMPUTE
  • If pTokens contains an entry of VK_INDIRECT_COMMANDS_TOKEN_TYPE_PIPELINE_NVX it must be the first element of the array and there must be only a single element of such token type.
  • All state binding tokens in pTokens must occur prior work provoking tokens (VK_INDIRECT_COMMANDS_TOKEN_TYPE_DRAW_NVX, VK_INDIRECT_COMMANDS_TOKEN_TYPE_DRAW_INDEXED_NVX, VK_INDIRECT_COMMANDS_TOKEN_TYPE_DISPATCH_NVX).
  • The content of pTokens must include one single work provoking token that is compatible with the pipelineBindPoint.

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_INDIRECT_COMMANDS_LAYOUT_CREATE_INFO_NVX
  • pNext must be NULL
  • pipelineBindPoint must be a valid VkPipelineBindPoint value
  • flags must be a valid combination of VkIndirectCommandsLayoutUsageFlagBitsNVX values
  • flags must not be 0
  • pTokens must be a valid pointer to an array of tokenCount valid VkIndirectCommandsLayoutTokenNVX structures
  • tokenCount must be greater than 0

See Also

VkIndirectCommandsLayoutTokenNVX, VkIndirectCommandsLayoutUsageFlagsNVX, VkPipelineBindPoint, VkStructureType, vkCreateIndirectCommandsLayoutNVX

Constructors

VkIndirectCommandsLayoutCreateInfoNVX 

Fields

data VkCmdProcessCommandsInfoNVX Source #

VkCmdProcessCommandsInfoNVX - Structure specifying parameters for the generation of commands

Valid Usage

  • The provided objectTable must include all objects referenced by the generation process.
  • indirectCommandsTokenCount must match the indirectCommandsLayout’s tokenCount.
  • The tokenType member of each entry in the pIndirectCommandsTokens array must match the values used at creation time of indirectCommandsLayout
  • If targetCommandBuffer is provided, it must have reserved command space.
  • If targetCommandBuffer is provided, the objectTable must match the reservation’s objectTable and must have had all referenced objects registered at reservation time.
  • If targetCommandBuffer is provided, the indirectCommandsLayout must match the reservation’s indirectCommandsLayout.
  • If targetCommandBuffer is provided, the maxSequencesCount must not exceed the reservation’s maxSequencesCount.
  • If sequencesCountBuffer is used, its usage flag must have VK_BUFFER_USAGE_INDIRECT_BUFFER_BIT bit set.
  • If sequencesCountBuffer is used, sequencesCountOffset must be aligned to VkDeviceGeneratedCommandsLimitsNVX::minSequenceCountBufferOffsetAlignment.
  • If sequencesIndexBuffer is used, its usage flag must have VK_BUFFER_USAGE_INDIRECT_BUFFER_BIT bit set.
  • If sequencesIndexBuffer is used, sequencesIndexOffset must be aligned to VkDeviceGeneratedCommandsLimitsNVX::minSequenceIndexBufferOffsetAlignment.

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_CMD_PROCESS_COMMANDS_INFO_NVX
  • pNext must be NULL
  • objectTable must be a valid VkObjectTableNVX handle
  • indirectCommandsLayout must be a valid VkIndirectCommandsLayoutNVX handle
  • pIndirectCommandsTokens must be a valid pointer to an array of indirectCommandsTokenCount valid VkIndirectCommandsTokenNVX structures
  • If targetCommandBuffer is not NULL, targetCommandBuffer must be a valid VkCommandBuffer handle
  • If sequencesCountBuffer is not VK_NULL_HANDLE, sequencesCountBuffer must be a valid VkBuffer handle
  • If sequencesIndexBuffer is not VK_NULL_HANDLE, sequencesIndexBuffer must be a valid VkBuffer handle
  • indirectCommandsTokenCount must be greater than 0
  • Each of indirectCommandsLayout, objectTable, sequencesCountBuffer, sequencesIndexBuffer, and targetCommandBuffer that are valid handles must have been created, allocated, or retrieved from the same VkDevice

Host Synchronization

  • Host access to objectTable must be externally synchronized
  • Host access to targetCommandBuffer must be externally synchronized

See Also

VkBuffer, VkCommandBuffer, VkDeviceSize, VkIndirectCommandsLayoutNVX, VkIndirectCommandsTokenNVX, VkObjectTableNVX, VkStructureType, vkCmdProcessCommandsNVX

Constructors

VkCmdProcessCommandsInfoNVX 

Fields

data VkCmdReserveSpaceForCommandsInfoNVX Source #

VkCmdReserveSpaceForCommandsInfoNVX - Structure specifying parameters for the reservation of command buffer space

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_CMD_RESERVE_SPACE_FOR_COMMANDS_INFO_NVX
  • pNext must be NULL
  • objectTable must be a valid VkObjectTableNVX handle
  • indirectCommandsLayout must be a valid VkIndirectCommandsLayoutNVX handle
  • Both of indirectCommandsLayout, and objectTable must have been created, allocated, or retrieved from the same VkDevice

Host Synchronization

  • Host access to objectTable must be externally synchronized

See Also

VkIndirectCommandsLayoutNVX, VkObjectTableNVX, VkStructureType, vkCmdReserveSpaceForCommandsNVX

Constructors

VkCmdReserveSpaceForCommandsInfoNVX 

Fields

data VkObjectTableCreateInfoNVX Source #

VkObjectTableCreateInfoNVX - Structure specifying the parameters of a newly created object table

Valid Usage

  • If the VkDeviceGeneratedCommandsFeaturesNVX::computeBindingPointSupport feature is not enabled, pObjectEntryUsageFlags must not contain VK_OBJECT_ENTRY_USAGE_COMPUTE_BIT_NVX
  • Any value within pObjectEntryCounts must not exceed VkDeviceGeneratedCommandsLimitsNVX::maxObjectEntryCounts
  • maxUniformBuffersPerDescriptor must be within the limits supported by the device.
  • maxStorageBuffersPerDescriptor must be within the limits supported by the device.
  • maxStorageImagesPerDescriptor must be within the limits supported by the device.
  • maxSampledImagesPerDescriptor must be within the limits supported by the device.

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_OBJECT_TABLE_CREATE_INFO_NVX
  • pNext must be NULL
  • pObjectEntryTypes must be a valid pointer to an array of objectCount valid VkObjectEntryTypeNVX values
  • pObjectEntryCounts must be a valid pointer to an array of objectCount uint32_t values
  • pObjectEntryUsageFlags must be a valid pointer to an array of objectCount valid combinations of VkObjectEntryUsageFlagBitsNVX values
  • Each element of pObjectEntryUsageFlags must not be 0
  • objectCount must be greater than 0

See Also

VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX, VkStructureType, vkCreateObjectTableNVX

Constructors

VkObjectTableCreateInfoNVX 

Fields

data VkObjectTableEntryNVX Source #

VkObjectTableEntryNVX - Common parameters of an object table resource entry

Valid Usage

  • If the VkDeviceGeneratedCommandsFeaturesNVX::computeBindingPointSupport feature is not enabled, flags must not contain VK_OBJECT_ENTRY_USAGE_COMPUTE_BIT_NVX

Valid Usage (Implicit)

See Also

VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX, vkRegisterObjectsNVX

Constructors

VkObjectTableEntryNVX 

Fields

data VkObjectTablePipelineEntryNVX Source #

VkObjectTablePipelineEntryNVX - Parameters of an object table pipeline entry

Valid Usage

  • type must be VK_OBJECT_ENTRY_TYPE_PIPELINE_NVX

Valid Usage (Implicit)

See Also

VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX, VkPipeline

Constructors

VkObjectTablePipelineEntryNVX 

Fields

data VkObjectTableDescriptorSetEntryNVX Source #

VkObjectTableDescriptorSetEntryNVX - Parameters of an object table descriptor set entry

Valid Usage

  • type must be VK_OBJECT_ENTRY_TYPE_DESCRIPTOR_SET_NVX

Valid Usage (Implicit)

  • flags must be a valid combination of VkObjectEntryUsageFlagBitsNVX values
  • flags must not be 0
  • pipelineLayout must be a valid VkPipelineLayout handle
  • descriptorSet must be a valid VkDescriptorSet handle
  • Both of descriptorSet, and pipelineLayout must have been created, allocated, or retrieved from the same VkDevice

See Also

VkDescriptorSet, VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX, VkPipelineLayout

Constructors

VkObjectTableDescriptorSetEntryNVX 

Fields

data VkObjectTableVertexBufferEntryNVX Source #

VkObjectTableVertexBufferEntryNVX - Parameters of an object table vertex buffer entry

Valid Usage

  • type must be VK_OBJECT_ENTRY_TYPE_VERTEX_BUFFER_NVX

Valid Usage (Implicit)

See Also

VkBuffer, VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX

Constructors

VkObjectTableVertexBufferEntryNVX 

Fields

data VkObjectTableIndexBufferEntryNVX Source #

VkObjectTableIndexBufferEntryNVX - Parameters of an object table index buffer entry

Valid Usage

  • type must be VK_OBJECT_ENTRY_TYPE_INDEX_BUFFER_NVX

Valid Usage (Implicit)

See Also

VkBuffer, VkIndexType, VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX

Constructors

VkObjectTableIndexBufferEntryNVX 

Fields

data VkObjectTablePushConstantEntryNVX Source #

VkObjectTablePushConstantEntryNVX - Parameters of an object table push constant entry

Valid Usage

  • type must be VK_OBJECT_ENTRY_TYPE_PUSH_CONSTANT_NVX

Valid Usage (Implicit)

See Also

VkObjectEntryTypeNVX, VkObjectEntryUsageFlagsNVX, VkPipelineLayout, VkShaderStageFlags

Constructors

VkObjectTablePushConstantEntryNVX 

Fields

type VkIndirectCommandsLayoutUsageFlagsNVX = VkIndirectCommandsLayoutUsageFlagBitsNVX Source #

VkIndirectCommandsLayoutUsageFlagsNVX - Bitmask of VkIndirectCommandsLayoutUsageFlagBitsNVX

Description

VkIndirectCommandsLayoutUsageFlagsNVX is a bitmask type for setting a mask of zero or more VkIndirectCommandsLayoutUsageFlagBitsNVX.

See Also

VkIndirectCommandsLayoutCreateInfoNVX, VkIndirectCommandsLayoutUsageFlagBitsNVX