Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- initializePerformanceApiINTEL :: forall io. MonadIO io => Device -> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL) -> io ()
- uninitializePerformanceApiINTEL :: forall io. MonadIO io => Device -> io ()
- cmdSetPerformanceMarkerINTEL :: forall io. MonadIO io => CommandBuffer -> PerformanceMarkerInfoINTEL -> io ()
- cmdSetPerformanceStreamMarkerINTEL :: forall io. MonadIO io => CommandBuffer -> PerformanceStreamMarkerInfoINTEL -> io ()
- cmdSetPerformanceOverrideINTEL :: forall io. MonadIO io => CommandBuffer -> PerformanceOverrideInfoINTEL -> io ()
- acquirePerformanceConfigurationINTEL :: forall io. MonadIO io => Device -> PerformanceConfigurationAcquireInfoINTEL -> io PerformanceConfigurationINTEL
- releasePerformanceConfigurationINTEL :: forall io. MonadIO io => Device -> PerformanceConfigurationINTEL -> io ()
- queueSetPerformanceConfigurationINTEL :: forall io. MonadIO io => Queue -> PerformanceConfigurationINTEL -> io ()
- getPerformanceParameterINTEL :: forall io. MonadIO io => Device -> PerformanceParameterTypeINTEL -> io PerformanceValueINTEL
- pattern STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: StructureType
- data PerformanceValueINTEL = PerformanceValueINTEL {}
- data InitializePerformanceApiInfoINTEL = InitializePerformanceApiInfoINTEL {}
- data QueryPoolPerformanceQueryCreateInfoINTEL = QueryPoolPerformanceQueryCreateInfoINTEL {}
- data PerformanceMarkerInfoINTEL = PerformanceMarkerInfoINTEL {}
- data PerformanceStreamMarkerInfoINTEL = PerformanceStreamMarkerInfoINTEL {}
- data PerformanceOverrideInfoINTEL = PerformanceOverrideInfoINTEL {}
- data PerformanceConfigurationAcquireInfoINTEL = PerformanceConfigurationAcquireInfoINTEL {}
- data PerformanceValueDataINTEL
- peekPerformanceValueDataINTEL :: PerformanceValueTypeINTEL -> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
- newtype PerformanceConfigurationTypeINTEL where
- newtype QueryPoolSamplingModeINTEL where
- newtype PerformanceOverrideTypeINTEL where
- newtype PerformanceParameterTypeINTEL where
- newtype PerformanceValueTypeINTEL where
- PerformanceValueTypeINTEL Int32
- pattern PERFORMANCE_VALUE_TYPE_UINT32_INTEL :: PerformanceValueTypeINTEL
- pattern PERFORMANCE_VALUE_TYPE_UINT64_INTEL :: PerformanceValueTypeINTEL
- pattern PERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: PerformanceValueTypeINTEL
- pattern PERFORMANCE_VALUE_TYPE_BOOL_INTEL :: PerformanceValueTypeINTEL
- pattern PERFORMANCE_VALUE_TYPE_STRING_INTEL :: PerformanceValueTypeINTEL
- type QueryPoolCreateInfoINTEL = QueryPoolPerformanceQueryCreateInfoINTEL
- type INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2
- pattern INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall a. Integral a => a
- type INTEL_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_INTEL_performance_query"
- pattern INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
- newtype PerformanceConfigurationINTEL = PerformanceConfigurationINTEL Word64
Documentation
initializePerformanceApiINTEL :: forall io. MonadIO io => Device -> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL) -> io () Source #
vkInitializePerformanceApiINTEL - Initialize a device for performance queries
Parameters
device
is the logical device used for the queries.
pInitializeInfo
is a pointer to aInitializePerformanceApiInfoINTEL
structure specifying initialization parameters.
Return Codes
See Also
uninitializePerformanceApiINTEL :: forall io. MonadIO io => Device -> io () Source #
vkUninitializePerformanceApiINTEL - Uninitialize a device for performance queries
Parameters
device
is the logical device used for the queries.
Valid Usage (Implicit)
See Also
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)
commandBuffer
must be a validCommandBuffer
handle
pMarkerInfo
must be a valid pointer to a validPerformanceMarkerInfoINTEL
structurecommandBuffer
must be in the recording state- The
CommandPool
thatcommandBuffer
was allocated from must support graphics, compute, or transfer operations
Host Synchronization
- Host access to the
CommandPool
thatcommandBuffer
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
See Also
cmdSetPerformanceStreamMarkerINTEL :: forall io. MonadIO io => CommandBuffer -> PerformanceStreamMarkerInfoINTEL -> io () Source #
vkCmdSetPerformanceStreamMarkerINTEL - Markers
Valid Usage (Implicit)
commandBuffer
must be a validCommandBuffer
handle
pMarkerInfo
must be a valid pointer to a validPerformanceStreamMarkerInfoINTEL
structurecommandBuffer
must be in the recording state- The
CommandPool
thatcommandBuffer
was allocated from must support graphics, compute, or transfer operations
Host Synchronization
- Host access to the
CommandPool
thatcommandBuffer
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
See Also
cmdSetPerformanceOverrideINTEL :: forall io. MonadIO io => CommandBuffer -> PerformanceOverrideInfoINTEL -> io () Source #
vkCmdSetPerformanceOverrideINTEL - Performance override settings
Parameters
commandBuffer
is the command buffer where the override takes place.
pOverrideInfo
is a pointer to aPerformanceOverrideInfoINTEL
structure selecting the parameter to override.
Valid Usage
pOverrideInfo
must not be used with aPerformanceOverrideTypeINTEL
that is not reported available bygetPerformanceParameterINTEL
Valid Usage (Implicit)
commandBuffer
must be a validCommandBuffer
handle
pOverrideInfo
must be a valid pointer to a validPerformanceOverrideInfoINTEL
structurecommandBuffer
must be in the recording state- The
CommandPool
thatcommandBuffer
was allocated from must support graphics, compute, or transfer operations
Host Synchronization
- Host access to the
CommandPool
thatcommandBuffer
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
See Also
acquirePerformanceConfigurationINTEL :: forall io. MonadIO io => Device -> PerformanceConfigurationAcquireInfoINTEL -> io PerformanceConfigurationINTEL Source #
vkAcquirePerformanceConfigurationINTEL - Acquire the performance query capability
Parameters
device
is the logical device that the performance query commands will be submitted to.
pAcquireInfo
is a pointer to aPerformanceConfigurationAcquireInfoINTEL
structure, specifying the performance configuration to acquire.pConfiguration
is a pointer to aPerformanceConfigurationINTEL
handle in which the resulting configuration object is returned.
Return Codes
See Also
Device
,
PerformanceConfigurationAcquireInfoINTEL
,
PerformanceConfigurationINTEL
releasePerformanceConfigurationINTEL :: forall io. MonadIO io => Device -> PerformanceConfigurationINTEL -> io () Source #
vkReleasePerformanceConfigurationINTEL - Release a configuration to capture performance data
Parameters
device
is the device associated to the configuration object to release.
configuration
is the configuration object to release.
Return Codes
See Also
queueSetPerformanceConfigurationINTEL :: forall io. MonadIO io => Queue -> PerformanceConfigurationINTEL -> io () Source #
vkQueueSetPerformanceConfigurationINTEL - Set a performance query
Parameters
queue
is the queue on which the configuration will be used.
configuration
is the configuration to use.
Valid Usage (Implicit)
queue
must be a validQueue
handle
configuration
must be a validPerformanceConfigurationINTEL
handle- Both of
configuration
, andqueue
must have been created, allocated, or retrieved from the sameDevice
Command Properties
'
Command Buffer Levels | Render Pass Scope | Supported Queue Types | Pipeline Type |
---|---|---|---|
- | - | Any | - |
Return Codes
See Also
getPerformanceParameterINTEL :: forall io. MonadIO io => Device -> PerformanceParameterTypeINTEL -> io PerformanceValueINTEL Source #
vkGetPerformanceParameterINTEL - Query performance capabilities of the device
Parameters
device
is the logical device to query.
parameter
is the parameter to query.pValue
is a pointer to aPerformanceValueINTEL
structure in which the type and value of the parameter are returned.
Return Codes
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
PerformanceValueINTEL | |
|
Instances
Show PerformanceValueINTEL Source # | |
Defined in Vulkan.Extensions.VK_INTEL_performance_query showsPrec :: Int -> PerformanceValueINTEL -> ShowS # show :: PerformanceValueINTEL -> String # showList :: [PerformanceValueINTEL] -> ShowS # | |
FromCStruct PerformanceValueINTEL Source # | |
ToCStruct PerformanceValueINTEL Source # | |
Defined in Vulkan.Extensions.VK_INTEL_performance_query withCStruct :: PerformanceValueINTEL -> (Ptr PerformanceValueINTEL -> IO b) -> IO b Source # pokeCStruct :: Ptr PerformanceValueINTEL -> PerformanceValueINTEL -> IO b -> IO b Source # withZeroCStruct :: (Ptr PerformanceValueINTEL -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr PerformanceValueINTEL -> IO b -> IO b Source # cStructSize :: Int Source # | |
Zero PerformanceValueINTEL Source # | |
data InitializePerformanceApiInfoINTEL Source #
VkInitializePerformanceApiInfoINTEL - Structure specifying parameters of initialize of the device
Valid Usage (Implicit)
See Also
Instances
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
QueryPoolPerformanceQueryCreateInfoINTEL | |
|
Instances
data PerformanceMarkerInfoINTEL Source #
VkPerformanceMarkerInfoINTEL - Structure specifying performance markers
Valid Usage (Implicit)
See Also
Instances
data PerformanceStreamMarkerInfoINTEL Source #
VkPerformanceStreamMarkerInfoINTEL - Structure specifying stream performance markers
Valid Usage
- The value written by the application into
marker
must only used the valid bits as reported bygetPerformanceParameterINTEL
with thePERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
Valid Usage (Implicit)
sType
must beSTRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL
pNext
must beNULL
See Also
Instances
data PerformanceOverrideInfoINTEL Source #
VkPerformanceOverrideInfoINTEL - Performance override info
Valid Usage (Implicit)
See Also
Bool32
, PerformanceOverrideTypeINTEL
,
StructureType
,
cmdSetPerformanceOverrideINTEL
PerformanceOverrideInfoINTEL | |
|
Instances
data PerformanceConfigurationAcquireInfoINTEL Source #
VkPerformanceConfigurationAcquireInfoINTEL - Acquire a configuration to capture performance data
Valid Usage (Implicit)
See Also
PerformanceConfigurationTypeINTEL
,
StructureType
,
acquirePerformanceConfigurationINTEL
PerformanceConfigurationAcquireInfoINTEL | |
|
Instances
data PerformanceValueDataINTEL Source #
Instances
Show PerformanceValueDataINTEL Source # | |
Defined in Vulkan.Extensions.VK_INTEL_performance_query showsPrec :: Int -> PerformanceValueDataINTEL -> ShowS # show :: PerformanceValueDataINTEL -> String # showList :: [PerformanceValueDataINTEL] -> ShowS # | |
ToCStruct PerformanceValueDataINTEL Source # | |
Defined in Vulkan.Extensions.VK_INTEL_performance_query withCStruct :: PerformanceValueDataINTEL -> (Ptr PerformanceValueDataINTEL -> IO b) -> IO b Source # pokeCStruct :: Ptr PerformanceValueDataINTEL -> PerformanceValueDataINTEL -> IO b -> IO b Source # withZeroCStruct :: (Ptr PerformanceValueDataINTEL -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr PerformanceValueDataINTEL -> IO b -> IO b Source # cStructSize :: Int Source # | |
Zero PerformanceValueDataINTEL Source # | |
peekPerformanceValueDataINTEL :: PerformanceValueTypeINTEL -> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL Source #
newtype PerformanceConfigurationTypeINTEL Source #
VkPerformanceConfigurationTypeINTEL - Type of performance configuration
See Also
pattern PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: PerformanceConfigurationTypeINTEL |
Instances
newtype QueryPoolSamplingModeINTEL Source #
VkQueryPoolSamplingModeINTEL - Enum specifying how performance queries should be captured
See Also
pattern QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: QueryPoolSamplingModeINTEL |
|
Instances
newtype PerformanceOverrideTypeINTEL Source #
pattern PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: PerformanceOverrideTypeINTEL |
|
pattern PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: PerformanceOverrideTypeINTEL |
|
Instances
newtype PerformanceParameterTypeINTEL Source #
VkPerformanceParameterTypeINTEL - Parameters that can be queried
See Also
pattern PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: PerformanceParameterTypeINTEL |
|
pattern PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: PerformanceParameterTypeINTEL |
|
Instances
newtype PerformanceValueTypeINTEL Source #
VkPerformanceValueTypeINTEL - Type of the parameters that can be queried
See Also
Instances
type INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2 Source #
pattern INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall a. Integral a => a Source #
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