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

Vulkan.Core10.Query

Synopsis

Documentation

createQueryPool Source #

Arguments

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

device is the logical device that creates the query pool.

-> QueryPoolCreateInfo a

pCreateInfo is a pointer to a QueryPoolCreateInfo structure containing the number and type of queries to be managed by the pool.

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

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

-> io QueryPool 

vkCreateQueryPool - Create a new query pool object

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, QueryPool, QueryPoolCreateInfo

withQueryPool :: forall a io r. (Extendss QueryPoolCreateInfo a, PokeChain a, MonadIO io) => Device -> QueryPoolCreateInfo a -> Maybe AllocationCallbacks -> (io QueryPool -> (QueryPool -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createQueryPool and destroyQueryPool

To ensure that destroyQueryPool 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.

destroyQueryPool Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the query pool.

-> QueryPool

queryPool is the query pool to destroy.

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

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

-> io () 

vkDestroyQueryPool - Destroy a query pool object

Valid Usage

  • All submitted commands that refer to queryPool must have completed execution
  • If AllocationCallbacks were provided when queryPool was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when queryPool was created, pAllocator must be NULL

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to queryPool must be externally synchronized

See Also

AllocationCallbacks, Device, QueryPool

getQueryPoolResults Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the query pool.

-> QueryPool

queryPool is the query pool managing the queries containing the desired results.

-> ("firstQuery" ::: Word32)

firstQuery is the initial query index.

-> ("queryCount" ::: Word32)

queryCount is the number of queries to read.

-> ("dataSize" ::: Word64)

dataSize is the size in bytes of the buffer pointed to by pData.

-> ("data" ::: Ptr ())

pData is a pointer to a user-allocated buffer where the results will be written

-> ("stride" ::: DeviceSize)

stride is the stride in bytes between results for individual queries within pData.

-> QueryResultFlags

flags is a bitmask of QueryResultFlagBits specifying how and when results are returned.

-> io Result 

vkGetQueryPoolResults - Copy results of queries in a query pool to a host memory region

Description

The range of queries read is defined by [firstQuery, firstQuery + queryCount - 1]. For pipeline statistics queries, each query index in the pool contains one integer value for each bit that is enabled in QueryPoolCreateInfo::pipelineStatistics when the pool is created.

If no bits are set in flags, and all requested queries are in the available state, results are written as an array of 32-bit unsigned integer values. The behavior when not all queries are available, is described below.

If QUERY_RESULT_64_BIT is not set and the result overflows a 32-bit value, the value may either wrap or saturate. Similarly, if QUERY_RESULT_64_BIT is set and the result overflows a 64-bit value, the value may either wrap or saturate.

If QUERY_RESULT_WAIT_BIT is set, Vulkan will wait for each query to be in the available state before retrieving the numerical results for that query. In this case, getQueryPoolResults is guaranteed to succeed and return SUCCESS if the queries become available in a finite time (i.e. if they have been issued and not reset). If queries will never finish (e.g. due to being reset but not issued), then getQueryPoolResults may not return in finite time.

If QUERY_RESULT_WAIT_BIT and QUERY_RESULT_PARTIAL_BIT are both not set then no result values are written to pData for queries that are in the unavailable state at the time of the call, and getQueryPoolResults returns NOT_READY. However, availability state is still written to pData for those queries if QUERY_RESULT_WITH_AVAILABILITY_BIT is set.

Note

Applications must take care to ensure that use of the QUERY_RESULT_WAIT_BIT bit has the desired effect.

For example, if a query has been used previously and a command buffer records the commands cmdResetQueryPool, cmdBeginQuery, and cmdEndQuery for that query, then the query will remain in the available state until resetQueryPool is called or the cmdResetQueryPool command executes on a queue. Applications can use fences or events to ensure that a query has already been reset before checking for its results or availability status. Otherwise, a stale value could be returned from a previous use of the query.

The above also applies when QUERY_RESULT_WAIT_BIT is used in combination with QUERY_RESULT_WITH_AVAILABILITY_BIT. In this case, the returned availability status may reflect the result of a previous use of the query unless resetQueryPool is called or the cmdResetQueryPool command has been executed since the last use of the query.

Note

Applications can double-buffer query pool usage, with a pool per frame, and reset queries at the end of the frame in which they are read.

If QUERY_RESULT_PARTIAL_BIT is set, QUERY_RESULT_WAIT_BIT is not set, and the query’s status is unavailable, an intermediate result value between zero and the final result value is written to pData for that query.

If QUERY_RESULT_WITH_AVAILABILITY_BIT is set, the final integer value written for each query is non-zero if the query’s status was available or zero if the status was unavailable. When QUERY_RESULT_WITH_AVAILABILITY_BIT is used, implementations must guarantee that if they return a non-zero availability value then the numerical results must be valid, assuming the results are not reset by a subsequent command.

Note

Satisfying this guarantee may require careful ordering by the application, e.g. to read the availability status before reading the results.

Valid Usage

  • firstQuery must be less than the number of queries in queryPool

Valid Usage (Implicit)

  • device must be a valid Device handle
  • queryPool must be a valid QueryPool handle
  • pData must be a valid pointer to an array of dataSize bytes
  • flags must be a valid combination of QueryResultFlagBits values
  • dataSize must be greater than 0
  • queryPool must have been created, allocated, or retrieved from device

Return Codes

Success
Failure

See Also

Device, DeviceSize, QueryPool, QueryResultFlags

data QueryPoolCreateInfo (es :: [Type]) Source #

VkQueryPoolCreateInfo - Structure specifying parameters of a newly created query pool

Description

pipelineStatistics is ignored if queryType is not QUERY_TYPE_PIPELINE_STATISTICS.

Valid Usage

Valid Usage (Implicit)

See Also

QueryPipelineStatisticFlags, QueryPoolCreateFlags, QueryType, StructureType, createQueryPool

Constructors

QueryPoolCreateInfo 

Fields

Instances

Instances details
Extensible QueryPoolCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Query

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). QueryPoolCreateInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). QueryPoolCreateInfo ds -> Chain es -> QueryPoolCreateInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends QueryPoolCreateInfo e => b) -> Maybe b Source #

Show (Chain es) => Show (QueryPoolCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Query

Generic (QueryPoolCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Query

Associated Types

type Rep (QueryPoolCreateInfo es) :: Type -> Type #

(Extendss QueryPoolCreateInfo es, PeekChain es) => FromCStruct (QueryPoolCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Query

(Extendss QueryPoolCreateInfo es, PokeChain es) => ToCStruct (QueryPoolCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Query

es ~ ('[] :: [Type]) => Zero (QueryPoolCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Query

type Rep (QueryPoolCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Query

newtype QueryPool Source #

Constructors

QueryPool Word64 

Instances

Instances details
Eq QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

Ord QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

Show QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

Storable QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

Zero QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

HasObjectType QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle QueryPool Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype QueryPoolCreateFlags Source #

VkQueryPoolCreateFlags - Reserved for future use

Description

QueryPoolCreateFlags is a bitmask type for setting a mask, but is currently reserved for future use.

See Also

QueryPoolCreateInfo

Instances

Instances details
Eq QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

Ord QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

Read QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

Show QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

Storable QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

Bits QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

Zero QueryPoolCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPoolCreateFlags

newtype QueryType Source #

Constructors

QueryType Int32 

Instances

Instances details
Eq QueryType Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryType

Ord QueryType Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryType

Read QueryType Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryType

Show QueryType Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryType

Storable QueryType Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryType

Zero QueryType Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryType

newtype QueryResultFlagBits Source #

VkQueryResultFlagBits - Bitmask specifying how and when query results are returned

See Also

QueryResultFlags

Bundled Patterns

pattern QUERY_RESULT_64_BIT :: QueryResultFlagBits

QUERY_RESULT_64_BIT specifies the results will be written as an array of 64-bit unsigned integer values. If this bit is not set, the results will be written as an array of 32-bit unsigned integer values.

pattern QUERY_RESULT_WAIT_BIT :: QueryResultFlagBits

QUERY_RESULT_WAIT_BIT specifies that Vulkan will wait for each query’s status to become available before retrieving its results.

pattern QUERY_RESULT_WITH_AVAILABILITY_BIT :: QueryResultFlagBits

QUERY_RESULT_WITH_AVAILABILITY_BIT specifies that the availability status accompanies the results.

pattern QUERY_RESULT_PARTIAL_BIT :: QueryResultFlagBits

QUERY_RESULT_PARTIAL_BIT specifies that returning partial results is acceptable.

Instances

Instances details
Eq QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

Ord QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

Read QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

Show QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

Storable QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

Bits QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

Zero QueryResultFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryResultFlagBits

newtype QueryPipelineStatisticFlagBits Source #

VkQueryPipelineStatisticFlagBits - Bitmask specifying queried pipeline statistics

Description

These values are intended to measure relative statistics on one implementation. Various device architectures will count these values differently. Any or all counters may be affected by the issues described in Query Operation.

Note

For example, tile-based rendering devices may need to replay the scene multiple times, affecting some of the counts.

If a pipeline has rasterizerDiscardEnable enabled, implementations may discard primitives after the final vertex processing stage. As a result, if rasterizerDiscardEnable is enabled, the clipping input and output primitives counters may not be incremented.

When a pipeline statistics query finishes, the result for that query is marked as available. The application can copy the result to a buffer (via cmdCopyQueryPoolResults), or request it be put into host memory (via getQueryPoolResults).

See Also

QueryPipelineStatisticFlags

Bundled Patterns

pattern QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT specifies that queries managed by the pool will count the number of vertices processed by the input assembly stage. Vertices corresponding to incomplete primitives may contribute to the count.

pattern QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT specifies that queries managed by the pool will count the number of primitives processed by the input assembly stage. If primitive restart is enabled, restarting the primitive topology has no effect on the count. Incomplete primitives may be counted.

pattern QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT specifies that queries managed by the pool will count the number of vertex shader invocations. This counter’s value is incremented each time a vertex shader is invoked.

pattern QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT specifies that queries managed by the pool will count the number of geometry shader invocations. This counter’s value is incremented each time a geometry shader is invoked. In the case of instanced geometry shaders, the geometry shader invocations count is incremented for each separate instanced invocation.

pattern QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT specifies that queries managed by the pool will count the number of primitives generated by geometry shader invocations. The counter’s value is incremented each time the geometry shader emits a primitive. Restarting primitive topology using the SPIR-V instructions OpEndPrimitive or OpEndStreamPrimitive has no effect on the geometry shader output primitives count.

pattern QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT specifies that queries managed by the pool will count the number of primitives processed by the Primitive Clipping stage of the pipeline. The counter’s value is incremented each time a primitive reaches the primitive clipping stage.

pattern QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT specifies that queries managed by the pool will count the number of primitives output by the Primitive Clipping stage of the pipeline. The counter’s value is incremented each time a primitive passes the primitive clipping stage. The actual number of primitives output by the primitive clipping stage for a particular input primitive is implementation-dependent but must satisfy the following conditions:

  • If at least one vertex of the input primitive lies inside the clipping volume, the counter is incremented by one or more.
  • Otherwise, the counter is incremented by zero or more.
pattern QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT specifies that queries managed by the pool will count the number of fragment shader invocations. The counter’s value is incremented each time the fragment shader is invoked.

pattern QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT specifies that queries managed by the pool will count the number of patches processed by the tessellation control shader. The counter’s value is incremented once for each patch for which a tessellation control shader is invoked.

pattern QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT specifies that queries managed by the pool will count the number of invocations of the tessellation evaluation shader. The counter’s value is incremented each time the tessellation evaluation shader is invoked.

pattern QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT :: QueryPipelineStatisticFlagBits

QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT specifies that queries managed by the pool will count the number of compute shader invocations. The counter’s value is incremented every time the compute shader is invoked. Implementations may skip the execution of certain compute shader invocations or execute additional compute shader invocations for implementation-dependent reasons as long as the results of rendering otherwise remain unchanged.

Instances

Instances details
Eq QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits

Ord QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits

Read QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits

Show QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits

Storable QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits

Bits QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits

Methods

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

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

xor :: QueryPipelineStatisticFlagBits -> QueryPipelineStatisticFlagBits -> QueryPipelineStatisticFlagBits #

complement :: QueryPipelineStatisticFlagBits -> QueryPipelineStatisticFlagBits #

shift :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

rotate :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

zeroBits :: QueryPipelineStatisticFlagBits #

bit :: Int -> QueryPipelineStatisticFlagBits #

setBit :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

clearBit :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

complementBit :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

testBit :: QueryPipelineStatisticFlagBits -> Int -> Bool #

bitSizeMaybe :: QueryPipelineStatisticFlagBits -> Maybe Int #

bitSize :: QueryPipelineStatisticFlagBits -> Int #

isSigned :: QueryPipelineStatisticFlagBits -> Bool #

shiftL :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

unsafeShiftL :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

shiftR :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

unsafeShiftR :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

rotateL :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

rotateR :: QueryPipelineStatisticFlagBits -> Int -> QueryPipelineStatisticFlagBits #

popCount :: QueryPipelineStatisticFlagBits -> Int #

Zero QueryPipelineStatisticFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits