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

Vulkan.Extensions.VK_INTEL_performance_query

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

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

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

Return Codes

Success
Failure

See Also

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

Return Codes

Success
Failure

See Also

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

Return Codes

Success
Failure

See Also

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 

vkAcquirePerformanceConfigurationINTEL - Acquire the performance query capability

Return Codes

Success
Failure

See Also

Device, PerformanceConfigurationAcquireInfoINTEL, 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

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 Levels Render Pass Scope Supported Queue Types Pipeline Type
- - Any -

Return Codes

Success
Failure

See Also

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

Device, PerformanceParameterTypeINTEL, PerformanceValueINTEL

data PerformanceValueINTEL Source #

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

Valid Usage (Implicit)

See Also

PerformanceValueDataINTEL, PerformanceValueTypeINTEL, getPerformanceParameterINTEL

Constructors

PerformanceValueINTEL 

Fields

Instances

Instances details
Show PerformanceValueINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Generic PerformanceValueINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Associated Types

type Rep PerformanceValueINTEL :: Type -> Type #

FromCStruct PerformanceValueINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

ToCStruct PerformanceValueINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Zero PerformanceValueINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep PerformanceValueINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep PerformanceValueINTEL = D1 ('MetaData "PerformanceValueINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "PerformanceValueINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "type'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PerformanceValueTypeINTEL) :*: S1 ('MetaSel ('Just "data'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PerformanceValueDataINTEL)))

data InitializePerformanceApiInfoINTEL Source #

VkInitializePerformanceApiInfoINTEL - Structure specifying parameters of initialize of the device

Valid Usage (Implicit)

See Also

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

Generic InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Associated Types

type Rep InitializePerformanceApiInfoINTEL :: Type -> Type #

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

type Rep InitializePerformanceApiInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep InitializePerformanceApiInfoINTEL = D1 ('MetaData "InitializePerformanceApiInfoINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "InitializePerformanceApiInfoINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "userData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr ()))))

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

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

Generic 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

type Rep QueryPoolPerformanceQueryCreateInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep QueryPoolPerformanceQueryCreateInfoINTEL = D1 ('MetaData "QueryPoolPerformanceQueryCreateInfoINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "QueryPoolPerformanceQueryCreateInfoINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "performanceCountersSampling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QueryPoolSamplingModeINTEL)))

data PerformanceMarkerInfoINTEL Source #

VkPerformanceMarkerInfoINTEL - Structure specifying performance markers

Valid Usage (Implicit)

See Also

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

Generic PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Associated Types

type Rep PerformanceMarkerInfoINTEL :: Type -> Type #

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

type Rep PerformanceMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep PerformanceMarkerInfoINTEL = D1 ('MetaData "PerformanceMarkerInfoINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "PerformanceMarkerInfoINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "marker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word64)))

data PerformanceStreamMarkerInfoINTEL Source #

VkPerformanceStreamMarkerInfoINTEL - Structure specifying stream performance markers

Valid Usage

Valid Usage (Implicit)

  • pNext must be NULL

See Also

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

Generic PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Associated Types

type Rep PerformanceStreamMarkerInfoINTEL :: Type -> Type #

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

type Rep PerformanceStreamMarkerInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep PerformanceStreamMarkerInfoINTEL = D1 ('MetaData "PerformanceStreamMarkerInfoINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "PerformanceStreamMarkerInfoINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "marker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))

data PerformanceOverrideInfoINTEL Source #

VkPerformanceOverrideInfoINTEL - Performance override info

Valid Usage (Implicit)

See Also

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

Generic PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

Associated Types

type Rep PerformanceOverrideInfoINTEL :: Type -> Type #

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

type Rep PerformanceOverrideInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep PerformanceOverrideInfoINTEL = D1 ('MetaData "PerformanceOverrideInfoINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "PerformanceOverrideInfoINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "type'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PerformanceOverrideTypeINTEL) :*: (S1 ('MetaSel ('Just "enable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "parameter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word64))))

data PerformanceConfigurationAcquireInfoINTEL Source #

VkPerformanceConfigurationAcquireInfoINTEL - Acquire a configuration to capture performance data

Valid Usage (Implicit)

See Also

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

Generic 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

type Rep PerformanceConfigurationAcquireInfoINTEL Source # 
Instance details

Defined in Vulkan.Extensions.VK_INTEL_performance_query

type Rep PerformanceConfigurationAcquireInfoINTEL = D1 ('MetaData "PerformanceConfigurationAcquireInfoINTEL" "Vulkan.Extensions.VK_INTEL_performance_query" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "PerformanceConfigurationAcquireInfoINTEL" 'PrefixI 'True) (S1 ('MetaSel ('Just "type'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PerformanceConfigurationTypeINTEL)))

newtype PerformanceConfigurationTypeINTEL Source #

VkPerformanceConfigurationTypeINTEL - Type of performance configuration

See Also

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

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

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

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

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

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