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

Vulkan.Extensions.VK_INTEL_performance_query

Description

Name

VK_INTEL_performance_query - device extension

VK_INTEL_performance_query

Name String
VK_INTEL_performance_query
Extension Type
Device extension
Registered Extension Number
211
Revision
2
Extension and Version Dependencies
  • Requires Vulkan 1.0
Special Use
Contact

Other Extension Metadata

Last Modified Date
2018-05-16
IP Status
No known IP claims.
Contributors
  • Lionel Landwerlin, Intel
  • Piotr Maciejewski, Intel

Description

This extension allows an application to capture performance data to be interpreted by a external application or library.

Such a library is available at : https://github.com/intel/metrics-discovery

Performance analysis tools such as Graphics Performance Analyzers make use of this extension and the metrics-discovery library to present the data in a human readable way.

New Object Types

New Commands

New Structures

New Unions

New Enums

New Enum Constants

Example Code

// A previously created device
VkDevice device;

// A queue derived from the device
VkQueue queue;

VkInitializePerformanceApiInfoINTEL performanceApiInfoIntel = {
  VK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL,
  NULL,
  NULL
};

vkInitializePerformanceApiINTEL(
  device,
  &performanceApiInfoIntel);

VkQueryPoolPerformanceQueryCreateInfoINTEL queryPoolIntel = {
  VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL,
  NULL,
  VK_QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL,
};

VkQueryPoolCreateInfo queryPoolCreateInfo = {
  VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO,
  &queryPoolIntel,
  0,
  VK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL,
  1,
  0
};

VkQueryPool queryPool;

VkResult result = vkCreateQueryPool(
  device,
  &queryPoolCreateInfo,
  NULL,
  &queryPool);

assert(VK_SUCCESS == result);

// A command buffer we want to record counters on
VkCommandBuffer commandBuffer;

VkCommandBufferBeginInfo commandBufferBeginInfo = {
  VK_STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO,
  NULL,
  VK_COMMAND_BUFFER_USAGE_ONE_TIME_SUBMIT_BIT,
  NULL
};

result = vkBeginCommandBuffer(commandBuffer, &commandBufferBeginInfo);

assert(VK_SUCCESS == result);

vkCmdResetQueryPool(
  commandBuffer,
  queryPool,
  0,
  1);

vkCmdBeginQuery(
  commandBuffer,
  queryPool,
  0,
  0);

// Perform the commands you want to get performance information on
// ...

// Perform a barrier to ensure all previous commands were complete before
// ending the query
vkCmdPipelineBarrier(commandBuffer,
  VK_PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT,
  VK_PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT,
  0,
  0,
  NULL,
  0,
  NULL,
  0,
  NULL);

vkCmdEndQuery(
  commandBuffer,
  queryPool,
  0);

result = vkEndCommandBuffer(commandBuffer);

assert(VK_SUCCESS == result);

VkPerformanceConfigurationAcquireInfoINTEL performanceConfigurationAcquireInfo = {
  VK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL,
  NULL,
  VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
};

VkPerformanceConfigurationINTEL performanceConfigurationIntel;

result = vkAcquirePerformanceConfigurationINTEL(
  device,
  &performanceConfigurationAcquireInfo,
  &performanceConfigurationIntel);

vkQueueSetPerformanceConfigurationINTEL(queue, performanceConfigurationIntel);

assert(VK_SUCCESS == result);

// Submit the command buffer and wait for its completion
// ...

result = vkReleasePerformanceConfigurationINTEL(
  device,
  performanceConfigurationIntel);

assert(VK_SUCCESS == result);

// Get the report size from metrics-discovery's QueryReportSize

result = vkGetQueryPoolResults(
  device,
  queryPool,
  0, 1, QueryReportSize,
  data, QueryReportSize, 0);

assert(VK_SUCCESS == result);

// The data can then be passed back to metrics-discovery from which
// human readable values can be queried.

Version History

  • Revision 2, 2020-03-06 (Lionel Landwerlin)

    • Rename VkQueryPoolCreateInfoINTEL in VkQueryPoolPerformanceQueryCreateInfoINTEL
  • Revision 1, 2018-05-16 (Lionel Landwerlin)

    • Initial revision

See Also

InitializePerformanceApiInfoINTEL, PerformanceConfigurationAcquireInfoINTEL, PerformanceConfigurationINTEL, PerformanceConfigurationTypeINTEL, PerformanceMarkerInfoINTEL, PerformanceOverrideInfoINTEL, PerformanceOverrideTypeINTEL, PerformanceParameterTypeINTEL, PerformanceStreamMarkerInfoINTEL, PerformanceValueDataINTEL, PerformanceValueINTEL, PerformanceValueTypeINTEL, QueryPoolCreateInfoINTEL, QueryPoolPerformanceQueryCreateInfoINTEL, QueryPoolSamplingModeINTEL, acquirePerformanceConfigurationINTEL, cmdSetPerformanceMarkerINTEL, cmdSetPerformanceOverrideINTEL, cmdSetPerformanceStreamMarkerINTEL, getPerformanceParameterINTEL, initializePerformanceApiINTEL, queueSetPerformanceConfigurationINTEL, releasePerformanceConfigurationINTEL, uninitializePerformanceApiINTEL

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

initializePerformanceApiINTEL Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device used for the queries.

device must be a valid Device handle

-> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)

pInitializeInfo is a pointer to a InitializePerformanceApiInfoINTEL structure specifying initialization parameters.

pInitializeInfo must be a valid pointer to a valid InitializePerformanceApiInfoINTEL structure

-> io () 

vkInitializePerformanceApiINTEL - Initialize a device for performance queries

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, Device, InitializePerformanceApiInfoINTEL

uninitializePerformanceApiINTEL Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device used for the queries.

device must be a valid Device handle

-> io () 

vkUninitializePerformanceApiINTEL - Uninitialize a device for performance queries

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, Device

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

vkCmdSetPerformanceMarkerINTEL - Markers

Parameters

The last marker set onto a command buffer before the end of a query will be part of the query result.

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 LevelsRender Pass ScopeSupported Queue Types
Primary Secondary Both Graphics Compute Transfer

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, CommandBuffer, PerformanceMarkerInfoINTEL

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

vkCmdSetPerformanceStreamMarkerINTEL - Markers

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 LevelsRender Pass ScopeSupported Queue Types
Primary Secondary Both Graphics Compute Transfer

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, CommandBuffer, PerformanceStreamMarkerInfoINTEL

cmdSetPerformanceOverrideINTEL Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer where the override takes place.

-> PerformanceOverrideInfoINTEL

pOverrideInfo is a pointer to a PerformanceOverrideInfoINTEL structure selecting the parameter to override.

-> io () 

vkCmdSetPerformanceOverrideINTEL - Performance override settings

Valid Usage

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 LevelsRender Pass ScopeSupported Queue Types
Primary Secondary Both Graphics Compute Transfer

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, CommandBuffer, PerformanceOverrideInfoINTEL

acquirePerformanceConfigurationINTEL Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that the performance query commands will be submitted to.

device must be a valid Device handle

-> PerformanceConfigurationAcquireInfoINTEL

pAcquireInfo is a pointer to a PerformanceConfigurationAcquireInfoINTEL structure, specifying the performance configuration to acquire.

pAcquireInfo must be a valid pointer to a valid PerformanceConfigurationAcquireInfoINTEL structure

-> io PerformanceConfigurationINTEL 

releasePerformanceConfigurationINTEL Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated to the configuration object to release.

-> PerformanceConfigurationINTEL

configuration is the configuration object to release.

-> io () 

vkReleasePerformanceConfigurationINTEL - Release a configuration to capture performance data

Valid Usage

  • configuration must not be released before all command buffers submitted while the configuration was set are in pending state

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If configuration is not NULL_HANDLE, configuration must be a valid PerformanceConfigurationINTEL handle
  • If configuration is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to configuration must be externally synchronized

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, Device, PerformanceConfigurationINTEL

queueSetPerformanceConfigurationINTEL Source #

Arguments

:: forall io. MonadIO io 
=> Queue

queue is the queue on which the configuration will be used.

-> PerformanceConfigurationINTEL

configuration is the configuration to use.

-> io () 

vkQueueSetPerformanceConfigurationINTEL - Set a performance query

Valid Usage (Implicit)

  • queue must be a valid Queue handle

Command Properties

'

Command Buffer LevelsRender Pass ScopeSupported Queue Types
--Any

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, PerformanceConfigurationINTEL, Queue

getPerformanceParameterINTEL Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device to query.

device must be a valid Device handle

-> PerformanceParameterTypeINTEL

parameter is the parameter to query.

parameter must be a valid PerformanceParameterTypeINTEL value

-> io PerformanceValueINTEL 

vkGetPerformanceParameterINTEL - Query performance capabilities of the device

Return Codes

Success
Failure

See Also

VK_INTEL_performance_query, Device, PerformanceParameterTypeINTEL, PerformanceValueINTEL

data PerformanceValueINTEL Source #

VkPerformanceValueINTEL - Container for value and types of parameters that can be queried

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, PerformanceValueDataINTEL, PerformanceValueTypeINTEL, getPerformanceParameterINTEL

Constructors

PerformanceValueINTEL 

Fields

data InitializePerformanceApiInfoINTEL Source #

VkInitializePerformanceApiInfoINTEL - Structure specifying parameters of initialize of the device

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, StructureType, initializePerformanceApiINTEL

Constructors

InitializePerformanceApiInfoINTEL 

Fields

  • userData :: Ptr ()

    pUserData is a pointer for application data.

Instances

Instances details
Show InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

FromCStruct InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

data QueryPoolPerformanceQueryCreateInfoINTEL Source #

VkQueryPoolPerformanceQueryCreateInfoINTEL - Structure specifying parameters to create a pool of performance queries

Members

To create a pool for Intel performance queries, set QueryPoolCreateInfo::queryType to QUERY_TYPE_PERFORMANCE_QUERY_INTEL and add a QueryPoolPerformanceQueryCreateInfoINTEL structure to the pNext chain of the QueryPoolCreateInfo structure.

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, QueryPoolSamplingModeINTEL, StructureType

Constructors

QueryPoolPerformanceQueryCreateInfoINTEL 

Fields

Instances

Instances details
Eq QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

FromCStruct QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

data PerformanceMarkerInfoINTEL Source #

VkPerformanceMarkerInfoINTEL - Structure specifying performance markers

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, StructureType, cmdSetPerformanceMarkerINTEL

Constructors

PerformanceMarkerInfoINTEL 

Fields

  • marker :: Word64

    marker is the marker value that will be recorded into the opaque query results.

Instances

Instances details
Eq PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

FromCStruct PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

data PerformanceStreamMarkerInfoINTEL Source #

VkPerformanceStreamMarkerInfoINTEL - Structure specifying stream performance markers

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL

See Also

VK_INTEL_performance_query, StructureType, cmdSetPerformanceStreamMarkerINTEL

Constructors

PerformanceStreamMarkerInfoINTEL 

Fields

  • marker :: Word32

    marker is the marker value that will be recorded into the reports consumed by an external application.

Instances

Instances details
Eq PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

FromCStruct PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

data PerformanceOverrideInfoINTEL Source #

VkPerformanceOverrideInfoINTEL - Performance override information

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, Bool32, PerformanceOverrideTypeINTEL, StructureType, cmdSetPerformanceOverrideINTEL

Constructors

PerformanceOverrideInfoINTEL 

Fields

Instances

Instances details
Eq PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

FromCStruct PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

data PerformanceConfigurationAcquireInfoINTEL Source #

VkPerformanceConfigurationAcquireInfoINTEL - Acquire a configuration to capture performance data

Valid Usage (Implicit)

See Also

VK_INTEL_performance_query, PerformanceConfigurationTypeINTEL, StructureType, acquirePerformanceConfigurationINTEL

Constructors

PerformanceConfigurationAcquireInfoINTEL 

Fields

Instances

Instances details
Eq PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

FromCStruct PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

newtype PerformanceConfigurationTypeINTEL Source #

VkPerformanceConfigurationTypeINTEL - Type of performance configuration

See Also

VK_INTEL_performance_query, PerformanceConfigurationAcquireInfoINTEL

Instances

Instances details
Eq PerformanceConfigurationTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Ord PerformanceConfigurationTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Read PerformanceConfigurationTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceConfigurationTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceConfigurationTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceConfigurationTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

newtype QueryPoolSamplingModeINTEL Source #

VkQueryPoolSamplingModeINTEL - Enum specifying how performance queries should be captured

See Also

VK_INTEL_performance_query, QueryPoolPerformanceQueryCreateInfoINTEL

Bundled Patterns

pattern QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: QueryPoolSamplingModeINTEL

QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL is the default mode in which the application calls cmdBeginQuery and cmdEndQuery to record performance data.

Instances

Instances details
Eq QueryPoolSamplingModeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Ord QueryPoolSamplingModeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Read QueryPoolSamplingModeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show QueryPoolSamplingModeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable QueryPoolSamplingModeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero QueryPoolSamplingModeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

newtype PerformanceOverrideTypeINTEL Source #

VkPerformanceOverrideTypeINTEL - Performance override type

See Also

VK_INTEL_performance_query, PerformanceOverrideInfoINTEL

Bundled Patterns

pattern PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: PerformanceOverrideTypeINTEL

PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL turns all rendering operations into noop.

pattern PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: PerformanceOverrideTypeINTEL

PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL stalls the stream of commands until all previously emitted commands have completed and all caches been flushed and invalidated.

Instances

Instances details
Eq PerformanceOverrideTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Ord PerformanceOverrideTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Read PerformanceOverrideTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceOverrideTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceOverrideTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceOverrideTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

newtype PerformanceParameterTypeINTEL Source #

VkPerformanceParameterTypeINTEL - Parameters that can be queried

See Also

VK_INTEL_performance_query, getPerformanceParameterINTEL

Bundled Patterns

pattern PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: PerformanceParameterTypeINTEL

PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL has a boolean result which tells whether hardware counters can be captured.

pattern PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: PerformanceParameterTypeINTEL

PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL has a 32 bits integer result which tells how many bits can be written into the PerformanceValueINTEL value.

Instances

Instances details
Eq PerformanceParameterTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Ord PerformanceParameterTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Read PerformanceParameterTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceParameterTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceParameterTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceParameterTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

newtype PerformanceValueTypeINTEL Source #

VkPerformanceValueTypeINTEL - Type of the parameters that can be queried

See Also

VK_INTEL_performance_query, PerformanceValueINTEL

Instances

Instances details
Eq PerformanceValueTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Ord PerformanceValueTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Read PerformanceValueTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Show PerformanceValueTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Storable PerformanceValueTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceValueTypeINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type INTEL_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_INTEL_performance_query" Source #

pattern INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #

newtype PerformanceConfigurationINTEL Source #

VkPerformanceConfigurationINTEL - Device configuration for performance queries

See Also

VK_INTEL_performance_query, acquirePerformanceConfigurationINTEL, queueSetPerformanceConfigurationINTEL, releasePerformanceConfigurationINTEL

Instances

Instances details
Eq PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle PerformanceConfigurationINTEL Source # 
Instance details

Defined in Vulkan.Extensions.Handles