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

Vulkan.Extensions.VK_NV_device_generated_commands

Synopsis

Documentation

cmdExecuteGeneratedCommandsNV Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

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

-> ("isPreprocessed" ::: Bool)

isPreprocessed represents whether the input data has already been preprocessed on the device. If it is FALSE this command will implicitly trigger the preprocessing step, otherwise not.

-> GeneratedCommandsInfoNV

pGeneratedCommandsInfo is a pointer to an instance of the GeneratedCommandsInfoNV structure containing parameters affecting the generation of commands.

-> io () 

vkCmdExecuteGeneratedCommandsNV - Performs the generation and execution of commands on the device

Valid Usage

Valid Usage (Implicit)

  • pGeneratedCommandsInfo must be a valid pointer to a valid GeneratedCommandsInfoNV 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 inside of a render pass instance

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 Inside Graphics Compute

See Also

Bool32, CommandBuffer, GeneratedCommandsInfoNV

cmdPreprocessGeneratedCommandsNV Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer which does the preprocessing.

-> GeneratedCommandsInfoNV

pGeneratedCommandsInfo is a pointer to an instance of the GeneratedCommandsInfoNV structure containing parameters affecting the preprocessing step.

-> io () 

vkCmdPreprocessGeneratedCommandsNV - Performs preprocessing for generated commands

Valid Usage

  • commandBuffer must not be a protected command buffer

Valid Usage (Implicit)

  • pGeneratedCommandsInfo must be a valid pointer to a valid GeneratedCommandsInfoNV 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

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 Outside Graphics Compute

See Also

CommandBuffer, GeneratedCommandsInfoNV

cmdBindPipelineShaderGroupNV Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer that the pipeline will be bound to.

-> PipelineBindPoint

pipelineBindPoint is a PipelineBindPoint value specifying the bind point to which the pipeline will be bound.

-> Pipeline

pipeline is the pipeline to be bound.

-> ("groupIndex" ::: Word32)

groupIndex is the shader group to be bound.

-> io () 

vkCmdBindPipelineShaderGroupNV - Bind a pipeline object

Valid Usage

Valid Usage (Implicit)

  • pipelineBindPoint must be a valid PipelineBindPoint value
  • pipeline must be a valid Pipeline handle
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics, or compute operations
  • Both of commandBuffer, and pipeline 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 Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics Compute

See Also

CommandBuffer, Pipeline, PipelineBindPoint

getGeneratedCommandsMemoryRequirementsNV Source #

Arguments

:: forall a io. (Extendss MemoryRequirements2 a, PokeChain a, PeekChain a, MonadIO io) 
=> Device

device is the logical device that owns the buffer.

-> GeneratedCommandsMemoryRequirementsInfoNV

pInfo is a pointer to an instance of the GeneratedCommandsMemoryRequirementsInfoNV structure containing parameters required for the memory requirements query.

-> io (MemoryRequirements2 a) 

vkGetGeneratedCommandsMemoryRequirementsNV - Retrieve the buffer allocation requirements for generated commands

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

See Also

Device, GeneratedCommandsMemoryRequirementsInfoNV, MemoryRequirements2

createIndirectCommandsLayoutNV Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the indirect command layout.

-> IndirectCommandsLayoutCreateInfoNV

pCreateInfo is a pointer to an instance of the IndirectCommandsLayoutCreateInfoNV structure containing parameters affecting creation of the indirect command layout.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io IndirectCommandsLayoutNV 

vkCreateIndirectCommandsLayoutNV - Create an indirect command layout object

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, IndirectCommandsLayoutCreateInfoNV, IndirectCommandsLayoutNV

withIndirectCommandsLayoutNV :: forall io r. MonadIO io => Device -> IndirectCommandsLayoutCreateInfoNV -> Maybe AllocationCallbacks -> (io IndirectCommandsLayoutNV -> (IndirectCommandsLayoutNV -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createIndirectCommandsLayoutNV and destroyIndirectCommandsLayoutNV

To ensure that destroyIndirectCommandsLayoutNV is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

destroyIndirectCommandsLayoutNV Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the layout.

-> IndirectCommandsLayoutNV

indirectCommandsLayout is the layout to destroy.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io () 

vkDestroyIndirectCommandsLayoutNV - Destroy an indirect commands layout

Valid Usage

  • All submitted commands that refer to indirectCommandsLayout must have completed execution

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If indirectCommandsLayout is not NULL_HANDLE, indirectCommandsLayout must be a valid IndirectCommandsLayoutNV handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • If indirectCommandsLayout is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to indirectCommandsLayout must be externally synchronized

See Also

AllocationCallbacks, Device, IndirectCommandsLayoutNV

data PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source #

VkPhysicalDeviceDeviceGeneratedCommandsFeaturesNV - Structure describing the device-generated commands features that can be supported by an implementation

Members

The members of the PhysicalDeviceDeviceGeneratedCommandsFeaturesNV structure describe the following features:

Description

If the PhysicalDeviceDeviceGeneratedCommandsFeaturesNV structure is included in the pNext chain of PhysicalDeviceFeatures2, it is filled with values indicating whether the feature is supported. PhysicalDeviceDeviceGeneratedCommandsFeaturesNV can also be used in the pNext chain of DeviceCreateInfo to enable the features.

Valid Usage (Implicit)

See Also

Bool32, StructureType

Constructors

PhysicalDeviceDeviceGeneratedCommandsFeaturesNV 

Fields

Instances

Instances details
Eq PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero PhysicalDeviceDeviceGeneratedCommandsFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source #

VkPhysicalDeviceDeviceGeneratedCommandsPropertiesNV - Structure describing push descriptor limits that can be supported by an implementation

Valid Usage (Implicit)

See Also

StructureType

Constructors

PhysicalDeviceDeviceGeneratedCommandsPropertiesNV 

Fields

Instances

Instances details
Eq PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero PhysicalDeviceDeviceGeneratedCommandsPropertiesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data GraphicsShaderGroupCreateInfoNV Source #

VkGraphicsShaderGroupCreateInfoNV - Structure specifying override parameters for each shader group

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL
  • pStages must be a valid pointer to an array of stageCount valid PipelineShaderStageCreateInfo structures
  • stageCount must be greater than 0

See Also

GraphicsPipelineShaderGroupsCreateInfoNV, PipelineShaderStageCreateInfo, PipelineTessellationStateCreateInfo, PipelineVertexInputStateCreateInfo, StructureType

Constructors

GraphicsShaderGroupCreateInfoNV 

Fields

data GraphicsPipelineShaderGroupsCreateInfoNV Source #

VkGraphicsPipelineShaderGroupsCreateInfoNV - Structure specifying parameters of a newly created multi shader group pipeline

Description

When referencing shader groups by index, groups defined in the referenced pipelines are treated as if they were defined as additional entries in pGroups. They are appended in the order they appear in the pPipelines array and in the pGroups array when those pipelines were defined.

The application must maintain the lifetime of all such referenced pipelines based on the pipelines that make use of them.

Valid Usage

  • The sum of groupCount including those groups added from referenced pPipelines must also be as maximum PhysicalDeviceDeviceGeneratedCommandsPropertiesNV::maxGraphicsShaderGroupCount
  • The state of the first element of pGroups must match its equivalent within the parent’s GraphicsPipelineCreateInfo
  • Each element of pGroups must in combination with the rest of the pipeline state yield a valid state configuration
  • All elements of pGroups must use the same shader stage combinations unless any mesh shader stage is used, then either combination of task and mesh or just mesh shader is valid
  • Mesh and regular primitive shading stages cannot be mixed across pGroups
  • Each element of the pPipelines member of libraries must have been created with identical state to the pipeline currently created except the state that can be overriden by GraphicsShaderGroupCreateInfoNV
  • The ::deviceGeneratedCommands feature must be enabled

Valid Usage (Implicit)

  • pGroups must be a valid pointer to an array of groupCount valid GraphicsShaderGroupCreateInfoNV structures
  • If pipelineCount is not 0, pPipelines must be a valid pointer to an array of pipelineCount valid Pipeline handles
  • groupCount must be greater than 0

See Also

GraphicsShaderGroupCreateInfoNV, Pipeline, StructureType

Constructors

GraphicsPipelineShaderGroupsCreateInfoNV 

Fields

data BindShaderGroupIndirectCommandNV Source #

VkBindShaderGroupIndirectCommandNV - Structure specifying input data for a single shader group command token

Valid Usage

  • The index must be within range of the accessible shader groups of the current bound graphics pipeline. See cmdBindPipelineShaderGroupNV for further details

See Also

No cross-references are available

Instances

Instances details
Eq BindShaderGroupIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show BindShaderGroupIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable BindShaderGroupIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct BindShaderGroupIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct BindShaderGroupIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero BindShaderGroupIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data BindIndexBufferIndirectCommandNV Source #

VkBindIndexBufferIndirectCommandNV - Structure specifying input data for a single index buffer command token

Valid Usage

  • The bufferAddress must be aligned to the indexType used
  • Each element of the buffer from which the address was acquired and that is non-sparse must be bound completely and contiguously to a single DeviceMemory object

Valid Usage (Implicit)

See Also

DeviceAddress, IndexType

Constructors

BindIndexBufferIndirectCommandNV 

Fields

Instances

Instances details
Eq BindIndexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show BindIndexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable BindIndexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct BindIndexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct BindIndexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero BindIndexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data BindVertexBufferIndirectCommandNV Source #

VkBindVertexBufferIndirectCommandNV - Structure specifying input data for a single vertex buffer command token

Valid Usage

  • Each element of the buffer from which the address was acquired and that is non-sparse must be bound completely and contiguously to a single DeviceMemory object

See Also

DeviceAddress

Constructors

BindVertexBufferIndirectCommandNV 

Fields

Instances

Instances details
Eq BindVertexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show BindVertexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable BindVertexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct BindVertexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct BindVertexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero BindVertexBufferIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data SetStateFlagsIndirectCommandNV Source #

VkSetStateFlagsIndirectCommandNV - Structure specifying input data for a single state flag command token

See Also

No cross-references are available

Constructors

SetStateFlagsIndirectCommandNV 

Fields

Instances

Instances details
Eq SetStateFlagsIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show SetStateFlagsIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable SetStateFlagsIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct SetStateFlagsIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct SetStateFlagsIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero SetStateFlagsIndirectCommandNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data IndirectCommandsStreamNV Source #

VkIndirectCommandsStreamNV - Structure specifying input streams for generated command tokens

Valid Usage

Valid Usage (Implicit)

  • buffer must be a valid Buffer handle

See Also

Buffer, DeviceSize, GeneratedCommandsInfoNV

Constructors

IndirectCommandsStreamNV 

Fields

  • buffer :: Buffer

    buffer specifies the Buffer storing the functional arguments for each sequence. These arguments can be written by the device.

  • offset :: DeviceSize

    offset specified an offset into buffer where the arguments start.

Instances

Instances details
Eq IndirectCommandsStreamNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show IndirectCommandsStreamNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable IndirectCommandsStreamNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct IndirectCommandsStreamNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct IndirectCommandsStreamNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero IndirectCommandsStreamNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

data IndirectCommandsLayoutTokenNV Source #

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

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL
  • tokenType must be a valid IndirectCommandsTokenTypeNV value
  • If pushconstantPipelineLayout is not NULL_HANDLE, pushconstantPipelineLayout must be a valid PipelineLayout handle
  • pushconstantShaderStageFlags must be a valid combination of ShaderStageFlagBits values
  • indirectStateFlags must be a valid combination of IndirectStateFlagBitsNV values
  • If indexTypeCount is not 0, pIndexTypes must be a valid pointer to an array of indexTypeCount valid IndexType values
  • If indexTypeCount is not 0, pIndexTypeValues must be a valid pointer to an array of indexTypeCount uint32_t values

See Also

Bool32, IndexType, IndirectCommandsLayoutCreateInfoNV, IndirectCommandsTokenTypeNV, IndirectStateFlagsNV, PipelineLayout, ShaderStageFlags, StructureType

Constructors

IndirectCommandsLayoutTokenNV 

Fields

data IndirectCommandsLayoutCreateInfoNV Source #

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

Description

The following code illustrates some of the flags:

void cmdProcessAllSequences(cmd, pipeline, indirectCommandsLayout, pIndirectCommandsTokens, sequencesCount, indexbuffer, indexbufferOffset)
{
  for (s = 0; s < sequencesCount; s++)
  {
    sUsed = s;

    if (indirectCommandsLayout.flags & VK_INDIRECT_COMMANDS_LAYOUT_USAGE_INDEXED_SEQUENCES_BIT_NV) {
      sUsed = indexbuffer.load_uint32( sUsed * sizeof(uint32_t) + indexbufferOffset);
    }

    if (indirectCommandsLayout.flags & VK_INDIRECT_COMMANDS_LAYOUT_USAGE_UNORDERED_SEQUENCES_BIT_NV) {
      sUsed = incoherent_implementation_dependent_permutation[ sUsed ];
    }

    cmdProcessSequence( cmd, pipeline, indirectCommandsLayout, pIndirectCommandsTokens, sUsed );
  }
}

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL
  • flags must be a valid combination of IndirectCommandsLayoutUsageFlagBitsNV values
  • flags must not be 0
  • pipelineBindPoint must be a valid PipelineBindPoint value
  • pTokens must be a valid pointer to an array of tokenCount valid IndirectCommandsLayoutTokenNV structures
  • pStreamStrides must be a valid pointer to an array of streamCount uint32_t values
  • tokenCount must be greater than 0
  • streamCount must be greater than 0

See Also

IndirectCommandsLayoutTokenNV, IndirectCommandsLayoutUsageFlagsNV, PipelineBindPoint, StructureType, createIndirectCommandsLayoutNV

Constructors

IndirectCommandsLayoutCreateInfoNV 

Fields

data GeneratedCommandsInfoNV Source #

VkGeneratedCommandsInfoNV - Structure specifying parameters for the generation of commands

Valid Usage

  • The provided pipeline must match the pipeline bound at execution time

Valid Usage (Implicit)

  • pNext must be NULL
  • pipelineBindPoint must be a valid PipelineBindPoint value
  • pipeline must be a valid Pipeline handle
  • indirectCommandsLayout must be a valid IndirectCommandsLayoutNV handle
  • pStreams must be a valid pointer to an array of streamCount valid IndirectCommandsStreamNV structures
  • preprocessBuffer must be a valid Buffer handle
  • If sequencesCountBuffer is not NULL_HANDLE, sequencesCountBuffer must be a valid Buffer handle
  • If sequencesIndexBuffer is not NULL_HANDLE, sequencesIndexBuffer must be a valid Buffer handle
  • streamCount must be greater than 0
  • Each of indirectCommandsLayout, pipeline, preprocessBuffer, sequencesCountBuffer, and sequencesIndexBuffer that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

See Also

Buffer, DeviceSize, IndirectCommandsLayoutNV, IndirectCommandsStreamNV, Pipeline, PipelineBindPoint, StructureType, cmdExecuteGeneratedCommandsNV, cmdPreprocessGeneratedCommandsNV

Constructors

GeneratedCommandsInfoNV 

Fields

data GeneratedCommandsMemoryRequirementsInfoNV Source #

VkGeneratedCommandsMemoryRequirementsInfoNV - Structure specifying parameters for the reservation of preprocess buffer space

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL
  • pipelineBindPoint must be a valid PipelineBindPoint value
  • pipeline must be a valid Pipeline handle
  • indirectCommandsLayout must be a valid IndirectCommandsLayoutNV handle
  • Both of indirectCommandsLayout, and pipeline must have been created, allocated, or retrieved from the same Device

See Also

IndirectCommandsLayoutNV, Pipeline, PipelineBindPoint, StructureType, getGeneratedCommandsMemoryRequirementsNV

Constructors

GeneratedCommandsMemoryRequirementsInfoNV 

Fields

Instances

Instances details
Eq GeneratedCommandsMemoryRequirementsInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show GeneratedCommandsMemoryRequirementsInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable GeneratedCommandsMemoryRequirementsInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

FromCStruct GeneratedCommandsMemoryRequirementsInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

ToCStruct GeneratedCommandsMemoryRequirementsInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero GeneratedCommandsMemoryRequirementsInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

newtype IndirectCommandsLayoutUsageFlagBitsNV Source #

VkIndirectCommandsLayoutUsageFlagBitsNV - Bitmask specifying allowed usage of an indirect commands layout

See Also

IndirectCommandsLayoutUsageFlagsNV

Bundled Patterns

pattern INDIRECT_COMMANDS_LAYOUT_USAGE_EXPLICIT_PREPROCESS_BIT_NV :: IndirectCommandsLayoutUsageFlagBitsNV

INDIRECT_COMMANDS_LAYOUT_USAGE_EXPLICIT_PREPROCESS_BIT_NV specifies that the layout is always used with the manual preprocessing step through calling cmdPreprocessGeneratedCommandsNV and executed by cmdExecuteGeneratedCommandsNV with isPreprocessed set to TRUE.

pattern INDIRECT_COMMANDS_LAYOUT_USAGE_INDEXED_SEQUENCES_BIT_NV :: IndirectCommandsLayoutUsageFlagBitsNV

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

pattern INDIRECT_COMMANDS_LAYOUT_USAGE_UNORDERED_SEQUENCES_BIT_NV :: IndirectCommandsLayoutUsageFlagBitsNV

INDIRECT_COMMANDS_LAYOUT_USAGE_UNORDERED_SEQUENCES_BIT_NV specifies that the processing of sequences can happen at an implementation-dependent order, which is not: guaranteed to be coherent using the same input data.

Instances

Instances details
Eq IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Ord IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Read IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Bits IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Methods

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

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

xor :: IndirectCommandsLayoutUsageFlagBitsNV -> IndirectCommandsLayoutUsageFlagBitsNV -> IndirectCommandsLayoutUsageFlagBitsNV #

complement :: IndirectCommandsLayoutUsageFlagBitsNV -> IndirectCommandsLayoutUsageFlagBitsNV #

shift :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

rotate :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

zeroBits :: IndirectCommandsLayoutUsageFlagBitsNV #

bit :: Int -> IndirectCommandsLayoutUsageFlagBitsNV #

setBit :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

clearBit :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

complementBit :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

testBit :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> Bool #

bitSizeMaybe :: IndirectCommandsLayoutUsageFlagBitsNV -> Maybe Int #

bitSize :: IndirectCommandsLayoutUsageFlagBitsNV -> Int #

isSigned :: IndirectCommandsLayoutUsageFlagBitsNV -> Bool #

shiftL :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

unsafeShiftL :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

shiftR :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

unsafeShiftR :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

rotateL :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

rotateR :: IndirectCommandsLayoutUsageFlagBitsNV -> Int -> IndirectCommandsLayoutUsageFlagBitsNV #

popCount :: IndirectCommandsLayoutUsageFlagBitsNV -> Int #

Zero IndirectCommandsLayoutUsageFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

newtype IndirectStateFlagBitsNV Source #

VkIndirectStateFlagBitsNV - Bitmask specifiying state that can be altered on the device

See Also

IndirectStateFlagsNV

Bundled Patterns

pattern INDIRECT_STATE_FLAG_FRONTFACE_BIT_NV :: IndirectStateFlagBitsNV

INDIRECT_STATE_FLAG_FRONTFACE_BIT_NV allows to toggle the FrontFace rasterization state for subsequent draw operations.

Instances

Instances details
Eq IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Ord IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Read IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Bits IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero IndirectStateFlagBitsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

newtype IndirectCommandsTokenTypeNV Source #

Instances

Instances details
Eq IndirectCommandsTokenTypeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Ord IndirectCommandsTokenTypeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Read IndirectCommandsTokenTypeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Show IndirectCommandsTokenTypeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Storable IndirectCommandsTokenTypeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

Zero IndirectCommandsTokenTypeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_device_generated_commands

type NV_DEVICE_GENERATED_COMMANDS_EXTENSION_NAME = "VK_NV_device_generated_commands" Source #

newtype IndirectCommandsLayoutNV Source #

VkIndirectCommandsLayoutNV - Opaque handle to an indirect commands layout object

See Also

GeneratedCommandsInfoNV, GeneratedCommandsMemoryRequirementsInfoNV, createIndirectCommandsLayoutNV, destroyIndirectCommandsLayoutNV

Instances

Instances details
Eq IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle IndirectCommandsLayoutNV Source # 
Instance details

Defined in Vulkan.Extensions.Handles