Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR :: forall io. MonadIO io => PhysicalDevice -> ("queueFamilyIndex" ::: Word32) -> io (Result, "counters" ::: Vector PerformanceCounterKHR, "counterDescriptions" ::: Vector PerformanceCounterDescriptionKHR)
- getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR :: forall io. MonadIO io => PhysicalDevice -> ("performanceQueryCreateInfo" ::: QueryPoolPerformanceCreateInfoKHR) -> io ("numPasses" ::: Word32)
- acquireProfilingLockKHR :: forall io. MonadIO io => Device -> AcquireProfilingLockInfoKHR -> io ()
- releaseProfilingLockKHR :: forall io. MonadIO io => Device -> io ()
- data PhysicalDevicePerformanceQueryFeaturesKHR = PhysicalDevicePerformanceQueryFeaturesKHR {}
- data PhysicalDevicePerformanceQueryPropertiesKHR = PhysicalDevicePerformanceQueryPropertiesKHR {}
- data PerformanceCounterKHR = PerformanceCounterKHR {}
- data PerformanceCounterDescriptionKHR = PerformanceCounterDescriptionKHR {}
- data QueryPoolPerformanceCreateInfoKHR = QueryPoolPerformanceCreateInfoKHR {}
- data AcquireProfilingLockInfoKHR = AcquireProfilingLockInfoKHR {}
- data PerformanceQuerySubmitInfoKHR = PerformanceQuerySubmitInfoKHR {}
- data PerformanceCounterResultKHR
- newtype PerformanceCounterScopeKHR where
- newtype PerformanceCounterUnitKHR where
- PerformanceCounterUnitKHR Int32
- pattern PERFORMANCE_COUNTER_UNIT_GENERIC_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_BYTES_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_KELVIN_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_WATTS_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_VOLTS_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_AMPS_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_HERTZ_KHR :: PerformanceCounterUnitKHR
- pattern PERFORMANCE_COUNTER_UNIT_CYCLES_KHR :: PerformanceCounterUnitKHR
- newtype PerformanceCounterStorageKHR where
- PerformanceCounterStorageKHR Int32
- pattern PERFORMANCE_COUNTER_STORAGE_INT32_KHR :: PerformanceCounterStorageKHR
- pattern PERFORMANCE_COUNTER_STORAGE_INT64_KHR :: PerformanceCounterStorageKHR
- pattern PERFORMANCE_COUNTER_STORAGE_UINT32_KHR :: PerformanceCounterStorageKHR
- pattern PERFORMANCE_COUNTER_STORAGE_UINT64_KHR :: PerformanceCounterStorageKHR
- pattern PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR :: PerformanceCounterStorageKHR
- pattern PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR :: PerformanceCounterStorageKHR
- newtype PerformanceCounterDescriptionFlagBitsKHR where
- type PerformanceCounterDescriptionFlagsKHR = PerformanceCounterDescriptionFlagBitsKHR
- newtype AcquireProfilingLockFlagBitsKHR = AcquireProfilingLockFlagBitsKHR Flags
- type AcquireProfilingLockFlagsKHR = AcquireProfilingLockFlagBitsKHR
- type KHR_PERFORMANCE_QUERY_SPEC_VERSION = 1
- pattern KHR_PERFORMANCE_QUERY_SPEC_VERSION :: forall a. Integral a => a
- type KHR_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_KHR_performance_query"
- pattern KHR_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
Documentation
enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR Source #
:: forall io. MonadIO io | |
=> PhysicalDevice |
|
-> ("queueFamilyIndex" ::: Word32) |
|
-> io (Result, "counters" ::: Vector PerformanceCounterKHR, "counterDescriptions" ::: Vector PerformanceCounterDescriptionKHR) |
vkEnumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR - Reports properties of the performance query counters available on a queue family of a device
Description
If pCounters
is NULL
and pCounterDescriptions
is NULL
, then the
number of counters available is returned in pCounterCount
. Otherwise,
pCounterCount
must point to a variable set by the user to the number
of elements in the pCounters
, pCounterDescriptions
, or both arrays
and on return the variable is overwritten with the number of structures
actually written out. If pCounterCount
is less than the number of
counters available, at most pCounterCount
structures will be written
and INCOMPLETE
will be returned instead of
SUCCESS
.
Valid Usage (Implicit)
physicalDevice
must be a validPhysicalDevice
handle
pCounterCount
must be a valid pointer to auint32_t
value- If the value referenced by
pCounterCount
is not0
, andpCounters
is notNULL
,pCounters
must be a valid pointer to an array ofpCounterCount
PerformanceCounterKHR
structures - If the value referenced by
pCounterCount
is not0
, andpCounterDescriptions
is notNULL
,pCounterDescriptions
must be a valid pointer to an array ofpCounterCount
PerformanceCounterDescriptionKHR
structures
Return Codes
See Also
PerformanceCounterDescriptionKHR
, PerformanceCounterKHR
,
PhysicalDevice
getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR Source #
:: forall io. MonadIO io | |
=> PhysicalDevice |
|
-> ("performanceQueryCreateInfo" ::: QueryPoolPerformanceCreateInfoKHR) |
|
-> io ("numPasses" ::: Word32) |
vkGetPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR - Reports the number of passes require for a performance query pool type
Description
The pPerformanceQueryCreateInfo
member
QueryPoolPerformanceCreateInfoKHR
::queueFamilyIndex
must be a
queue family of physicalDevice
. The number of passes required to
capture the counters specified in the pPerformanceQueryCreateInfo
member QueryPoolPerformanceCreateInfoKHR
::pCounters
is returned in
pNumPasses
.
Valid Usage (Implicit)
See Also
acquireProfilingLockKHR Source #
:: forall io. MonadIO io | |
=> Device |
|
-> AcquireProfilingLockInfoKHR |
|
-> io () |
vkAcquireProfilingLockKHR - Acquires the profiling lock
Description
Implementations may allow multiple actors to hold the profiling lock concurrently.
Return Codes
See Also
releaseProfilingLockKHR Source #
vkReleaseProfilingLockKHR - Releases the profiling lock
Valid Usage
- The profiling lock of
device
must have been held via a previous successful call toacquireProfilingLockKHR
Valid Usage (Implicit)
device
must be a validDevice
handle
See Also
data PhysicalDevicePerformanceQueryFeaturesKHR Source #
VkPhysicalDevicePerformanceQueryFeaturesKHR - Structure describing performance query support for an implementation
Valid Usage (Implicit)
See Also
PhysicalDevicePerformanceQueryFeaturesKHR | |
|
Instances
data PhysicalDevicePerformanceQueryPropertiesKHR Source #
VkPhysicalDevicePerformanceQueryPropertiesKHR - Structure describing performance query properties for an implementation
Members
The members of the PhysicalDevicePerformanceQueryPropertiesKHR
structure describe the following implementation-dependent properties:
Valid Usage (Implicit)
If the PhysicalDevicePerformanceQueryPropertiesKHR
structure is
included in the pNext
chain of
PhysicalDeviceProperties2
,
it is filled with the implementation-dependent properties.
See Also
PhysicalDevicePerformanceQueryPropertiesKHR | |
|
Instances
data PerformanceCounterKHR Source #
VkPerformanceCounterKHR - Structure providing information about a counter
Valid Usage (Implicit)
See Also
PerformanceCounterScopeKHR
, PerformanceCounterStorageKHR
,
PerformanceCounterUnitKHR
,
StructureType
,
enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR
PerformanceCounterKHR | |
|
Instances
data PerformanceCounterDescriptionKHR Source #
VkPerformanceCounterDescriptionKHR - Structure providing more detailed information about a counter
Valid Usage (Implicit)
See Also
PerformanceCounterDescriptionFlagsKHR
,
StructureType
,
enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR
PerformanceCounterDescriptionKHR | |
|
Instances
data QueryPoolPerformanceCreateInfoKHR Source #
VkQueryPoolPerformanceCreateInfoKHR - Structure specifying parameters of a newly created performance query pool
Valid Usage
queueFamilyIndex
must be a valid queue family index of the device
- The performanceCounterQueryPools feature must be enabled
- Each element of
pCounterIndices
must be in the range of counters reported byenumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR
for the queue family specified inqueueFamilyIndex
Valid Usage (Implicit)
sType
must beSTRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_CREATE_INFO_KHR
pCounterIndices
must be a valid pointer to an array ofcounterIndexCount
uint32_t
valuescounterIndexCount
must be greater than0
See Also
StructureType
,
getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR
QueryPoolPerformanceCreateInfoKHR | |
|
Instances
data AcquireProfilingLockInfoKHR Source #
VkAcquireProfilingLockInfoKHR - Structure specifying parameters to acquire the profiling lock
Valid Usage (Implicit)
If timeout
is 0, acquireProfilingLockKHR
will not block while
attempting to acquire the profling lock. If timeout
is UINT64_MAX
,
the function will not return until the profiling lock was acquired.
See Also
AcquireProfilingLockFlagsKHR
,
StructureType
,
acquireProfilingLockKHR
AcquireProfilingLockInfoKHR | |
|
Instances
data PerformanceQuerySubmitInfoKHR Source #
VkPerformanceQuerySubmitInfoKHR - Structure indicating which counter pass index is active for performance queries
Description
If the SubmitInfo
::pNext
chain does not include
this structure, the batch defaults to use counter pass index 0.
Valid Usage (Implicit)
See Also
PerformanceQuerySubmitInfoKHR | |
|
Instances
data PerformanceCounterResultKHR Source #
Int32Counter Int32 | |
Int64Counter Int64 | |
Uint32Counter Word32 | |
Uint64Counter Word64 | |
Float32Counter Float | |
Float64Counter Double |
Instances
Show PerformanceCounterResultKHR Source # | |
Defined in Vulkan.Extensions.VK_KHR_performance_query showsPrec :: Int -> PerformanceCounterResultKHR -> ShowS # show :: PerformanceCounterResultKHR -> String # showList :: [PerformanceCounterResultKHR] -> ShowS # | |
ToCStruct PerformanceCounterResultKHR Source # | |
Defined in Vulkan.Extensions.VK_KHR_performance_query withCStruct :: PerformanceCounterResultKHR -> (Ptr PerformanceCounterResultKHR -> IO b) -> IO b Source # pokeCStruct :: Ptr PerformanceCounterResultKHR -> PerformanceCounterResultKHR -> IO b -> IO b Source # withZeroCStruct :: (Ptr PerformanceCounterResultKHR -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr PerformanceCounterResultKHR -> IO b -> IO b Source # cStructSize :: Int Source # | |
Zero PerformanceCounterResultKHR Source # | |
newtype PerformanceCounterScopeKHR Source #
pattern PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR :: PerformanceCounterScopeKHR |
|
pattern PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR :: PerformanceCounterScopeKHR |
|
pattern PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR :: PerformanceCounterScopeKHR |
|
Instances
newtype PerformanceCounterUnitKHR Source #
Instances
newtype PerformanceCounterStorageKHR Source #
Instances
newtype PerformanceCounterDescriptionFlagBitsKHR Source #
VkPerformanceCounterDescriptionFlagBitsKHR - Bitmask specifying usage behavior for a counter
See Also
pattern PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR :: PerformanceCounterDescriptionFlagBitsKHR |
|
pattern PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR :: PerformanceCounterDescriptionFlagBitsKHR |
|
Instances
newtype AcquireProfilingLockFlagBitsKHR Source #
Instances
type KHR_PERFORMANCE_QUERY_SPEC_VERSION = 1 Source #
pattern KHR_PERFORMANCE_QUERY_SPEC_VERSION :: forall a. Integral a => a Source #
type KHR_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_KHR_performance_query" Source #
pattern KHR_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #