{-# language CPP #-}
-- No documentation found for Chapter "Query"
module Vulkan.Core10.Query  ( createQueryPool
                            , withQueryPool
                            , destroyQueryPool
                            , getQueryPoolResults
                            , QueryPoolCreateInfo(..)
                            , QueryPool(..)
                            , QueryPoolCreateFlags(..)
                            , QueryType(..)
                            , QueryResultFlagBits(..)
                            , QueryResultFlags
                            , QueryPipelineStatisticFlagBits(..)
                            , QueryPipelineStatisticFlags
                            ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Foreign.C.Types (CSize(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(CSize))
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCreateQueryPool))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyQueryPool))
import Vulkan.Dynamic (DeviceCmds(pVkGetQueryPoolResults))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits (QueryPipelineStatisticFlags)
import Vulkan.Core10.Handles (QueryPool)
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Enums.QueryPoolCreateFlags (QueryPoolCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_performance_query (QueryPoolPerformanceCreateInfoKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_INTEL_performance_query (QueryPoolPerformanceQueryCreateInfoINTEL)
import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlagBits(..))
import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlags)
import Vulkan.Core10.Enums.QueryType (QueryType)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits (QueryPipelineStatisticFlagBits(..))
import Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits (QueryPipelineStatisticFlags)
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Enums.QueryPoolCreateFlags (QueryPoolCreateFlags(..))
import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlagBits(..))
import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlags)
import Vulkan.Core10.Enums.QueryType (QueryType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateQueryPool
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct QueryPoolCreateInfo) -> Ptr AllocationCallbacks -> Ptr QueryPool -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct QueryPoolCreateInfo) -> Ptr AllocationCallbacks -> Ptr QueryPool -> IO Result

-- | vkCreateQueryPool - Create a new query pool object
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateQueryPool-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCreateQueryPool-pCreateInfo-parameter# @pCreateInfo@ /must/
--     be a valid pointer to a valid 'QueryPoolCreateInfo' structure
--
-- -   #VUID-vkCreateQueryPool-pAllocator-parameter# If @pAllocator@ is not
--     @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkCreateQueryPool-pQueryPool-parameter# @pQueryPool@ /must/ be
--     a valid pointer to a 'Vulkan.Core10.Handles.QueryPool' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.QueryPool',
-- 'QueryPoolCreateInfo'
createQueryPool :: forall a io
                 . (Extendss QueryPoolCreateInfo a, PokeChain a, MonadIO io)
                => -- | @device@ is the logical device that creates the query pool.
                   Device
                -> -- | @pCreateInfo@ is a pointer to a 'QueryPoolCreateInfo' structure
                   -- containing the number and type of queries to be managed by the pool.
                   (QueryPoolCreateInfo a)
                -> -- | @pAllocator@ controls host memory allocation as described in the
                   -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                   -- chapter.
                   ("allocator" ::: Maybe AllocationCallbacks)
                -> io (QueryPool)
createQueryPool :: forall (a :: [*]) (io :: * -> *).
(Extendss QueryPoolCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> QueryPoolCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io QueryPool
createQueryPool Device
device QueryPoolCreateInfo a
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkCreateQueryPoolPtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pQueryPool" ::: Ptr QueryPool)
   -> IO Result)
vkCreateQueryPoolPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pQueryPool" ::: Ptr QueryPool)
      -> IO Result)
pVkCreateQueryPool (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pQueryPool" ::: Ptr QueryPool)
   -> IO Result)
vkCreateQueryPoolPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCreateQueryPool is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCreateQueryPool' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pQueryPool" ::: Ptr QueryPool)
-> IO Result
vkCreateQueryPool' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pQueryPool" ::: Ptr QueryPool)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pQueryPool" ::: Ptr QueryPool)
-> IO Result
mkVkCreateQueryPool FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pQueryPool" ::: Ptr QueryPool)
   -> IO Result)
vkCreateQueryPoolPtr
  Ptr (QueryPoolCreateInfo a)
pCreateInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (QueryPoolCreateInfo a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pQueryPool" ::: Ptr QueryPool
pPQueryPool <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @QueryPool Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateQueryPool" (Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pQueryPool" ::: Ptr QueryPool)
-> IO Result
vkCreateQueryPool'
                                                      (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                      (forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (QueryPoolCreateInfo a)
pCreateInfo)
                                                      "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
                                                      ("pQueryPool" ::: Ptr QueryPool
pPQueryPool))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  QueryPool
pQueryPool <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @QueryPool "pQueryPool" ::: Ptr QueryPool
pPQueryPool
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (QueryPool
pQueryPool)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createQueryPool' and 'destroyQueryPool'
--
-- To ensure that 'destroyQueryPool' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the last argument.
-- To just extract the pair pass '(,)' as the last argument.
--
withQueryPool :: forall a io r . (Extendss QueryPoolCreateInfo a, PokeChain a, MonadIO io) => Device -> QueryPoolCreateInfo a -> Maybe AllocationCallbacks -> (io QueryPool -> (QueryPool -> io ()) -> r) -> r
withQueryPool :: forall (a :: [*]) (io :: * -> *) r.
(Extendss QueryPoolCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> QueryPoolCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io QueryPool -> (QueryPool -> io ()) -> r)
-> r
withQueryPool Device
device QueryPoolCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io QueryPool -> (QueryPool -> io ()) -> r
b =
  io QueryPool -> (QueryPool -> io ()) -> r
b (forall (a :: [*]) (io :: * -> *).
(Extendss QueryPoolCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> QueryPoolCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io QueryPool
createQueryPool Device
device QueryPoolCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(QueryPool
o0) -> forall (io :: * -> *).
MonadIO io =>
Device
-> QueryPool
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyQueryPool Device
device QueryPool
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyQueryPool
  :: FunPtr (Ptr Device_T -> QueryPool -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> QueryPool -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroyQueryPool - Destroy a query pool object
--
-- == Valid Usage
--
-- -   #VUID-vkDestroyQueryPool-queryPool-00793# All submitted commands
--     that refer to @queryPool@ /must/ have completed execution
--
-- -   #VUID-vkDestroyQueryPool-queryPool-00794# If
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @queryPool@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   #VUID-vkDestroyQueryPool-queryPool-00795# If no
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @queryPool@ was created, @pAllocator@ /must/ be @NULL@
--
-- Note
--
-- Applications /can/ verify that @queryPool@ /can/ be destroyed by
-- checking that 'getQueryPoolResults'() without the
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT' flag
-- returns 'Vulkan.Core10.Enums.Result.SUCCESS' for all queries that are
-- used in command buffers submitted for execution.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDestroyQueryPool-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkDestroyQueryPool-queryPool-parameter# If @queryPool@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @queryPool@ /must/ be a
--     valid 'Vulkan.Core10.Handles.QueryPool' handle
--
-- -   #VUID-vkDestroyQueryPool-pAllocator-parameter# If @pAllocator@ is
--     not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkDestroyQueryPool-queryPool-parent# 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
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.QueryPool'
destroyQueryPool :: forall io
                  . (MonadIO io)
                 => -- | @device@ is the logical device that destroys the query pool.
                    Device
                 -> -- | @queryPool@ is the query pool to destroy.
                    QueryPool
                 -> -- | @pAllocator@ controls host memory allocation as described in the
                    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                    -- chapter.
                    ("allocator" ::: Maybe AllocationCallbacks)
                 -> io ()
destroyQueryPool :: forall (io :: * -> *).
MonadIO io =>
Device
-> QueryPool
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyQueryPool Device
device QueryPool
queryPool "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyQueryPoolPtr :: FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyQueryPoolPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> QueryPool
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyQueryPool (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyQueryPoolPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDestroyQueryPool is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkDestroyQueryPool' :: Ptr Device_T
-> QueryPool -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyQueryPool' = FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> QueryPool
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyQueryPool FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyQueryPoolPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroyQueryPool" (Ptr Device_T
-> QueryPool -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyQueryPool'
                                                  (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                  (QueryPool
queryPool)
                                                  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetQueryPoolResults
  :: FunPtr (Ptr Device_T -> QueryPool -> Word32 -> Word32 -> CSize -> Ptr () -> DeviceSize -> QueryResultFlags -> IO Result) -> Ptr Device_T -> QueryPool -> Word32 -> Word32 -> CSize -> Ptr () -> DeviceSize -> QueryResultFlags -> IO Result

-- | vkGetQueryPoolResults - Copy results of queries in a query pool to a
-- host memory region
--
-- = Description
--
-- Any results written for a query are written according to
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-memorylayout a layout dependent on the query type>.
--
-- 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. Behavior when not all queries are available is described
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-wait-bit-not-set below>.
--
-- If
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
-- is set, results for all queries in @queryPool@ identified by
-- @firstQuery@ and @queryCount@ are copied to @pData@, along with an extra
-- availability or status value written directly after the results of each
-- query and interpreted as an unsigned integer. A value of zero indicates
-- that the results are not yet available, otherwise the query is complete
-- and results are available. The size of the availability or status values
-- is 64 bits if
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set in
-- @flags@. Otherwise, it is 32 bits.
--
-- If @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@ is set, results for all queries
-- in @queryPool@ identified by @firstQuery@ and @queryCount@ are copied to
-- @pData@, along with an extra status value written directly after the
-- results of each query and interpreted as a signed integer. A value of
-- zero indicates that the results are not yet available. Positive values
-- indicate that the operations within the query completed successfully,
-- and the query results are valid. Negative values indicate that the
-- operations within the query completed unsuccessfully.
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryResultStatusKHR VkQueryResultStatusKHR>
-- defines specific meaning for values returned here, though
-- implementations are free to return other values.
--
-- Note
--
-- If
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
-- or @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@ is set, the layout of data in
-- the buffer is a /(result,availability)/ or /(result,status)/ pair for
-- each query returned, and @stride@ is the stride between each pair.
--
-- Results for any available query written by this command are final and
-- represent the final result of the query. If
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT' is
-- set, then for any query that is unavailable, an intermediate result
-- between zero and the final result value is written for that query.
-- Otherwise, any result written by this command is undefined.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set,
-- results and, if returned, availability or status values for all queries
-- are written as an array of 64-bit values. If the @queryPool@ was created
-- with 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
-- results for each query are written as an array of the type indicated by
-- 'Vulkan.Extensions.VK_KHR_performance_query.PerformanceCounterKHR'::@storage@
-- for the counter being queried. Otherwise, results and availability or
-- status values are written as an array of 32-bit values. If an unsigned
-- integer query’s value overflows the result type, the value /may/ either
-- wrap or saturate. If a signed integer query’s value overflows the result
-- type, the value is undefined. If a floating point query’s value is not
-- representable as the result type, the value is undefined.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' is
-- set, this command defines an execution dependency with any earlier
-- commands that writes one of the identified queries. The first
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes all instances of
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndQuery',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT',
-- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWriteTimestamp2',
-- and 'Vulkan.Core10.CommandBufferBuilding.cmdWriteTimestamp' that
-- reference any query in @queryPool@ indicated by @firstQuery@ and
-- @queryCount@. The second
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes the host operations of this command.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' is
-- not set, 'getQueryPoolResults' /may/ return
-- 'Vulkan.Core10.Enums.Result.NOT_READY' if there are queries in the
-- unavailable state.
--
-- Note
--
-- Applications /must/ take care to ensure that use of the
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.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
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResetQueryPool',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery', and
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndQuery' for that query, then
-- the query will remain in the available state until
-- 'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.resetQueryPool' is
-- called or the 'Vulkan.Core10.CommandBufferBuilding.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
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' is used
-- in combination with
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'.
-- In this case, the returned availability status /may/ reflect the result
-- of a previous use of the query unless
-- 'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.resetQueryPool' is
-- called or the 'Vulkan.Core10.CommandBufferBuilding.cmdResetQueryPool'
-- command has been executed since the last use of the query.
--
-- A similar situation can arise with the
-- @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@ flag.
--
-- 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.
--
-- == Valid Usage
--
-- -   #VUID-vkGetQueryPoolResults-None-09401# All queries used by the
--     command /must/ not be uninitialized
--
-- -   #VUID-vkGetQueryPoolResults-firstQuery-00813# @firstQuery@ /must/ be
--     less than the number of queries in @queryPool@
--
-- -   #VUID-vkGetQueryPoolResults-flags-02828# If
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is not
--     set in @flags@ and the @queryType@ used to create @queryPool@ was
--     not
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     then @pData@ and @stride@ /must/ be multiples of @4@
--
-- -   #VUID-vkGetQueryPoolResults-flags-00815# If
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set
--     in @flags@ then @pData@ and @stride@ /must/ be multiples of @8@
--
-- -   #VUID-vkGetQueryPoolResults-stride-08993# If
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
--     is set, @stride@ /must/ be large enough to contain the unsigned
--     integer representing availability or status in addition to the query
--     result.
--
-- -   #VUID-vkGetQueryPoolResults-queryType-03229# If the @queryType@ used
--     to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     then @pData@ and @stride@ /must/ be multiples of the size of
--     'Vulkan.Extensions.VK_KHR_performance_query.PerformanceCounterResultKHR'
--
-- -   #VUID-vkGetQueryPoolResults-queryType-04519# If the @queryType@ used
--     to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     then @stride@ /must/ be large enough to contain the
--     'Vulkan.Extensions.VK_KHR_performance_query.QueryPoolPerformanceCreateInfoKHR'::@counterIndexCount@
--     used to create @queryPool@ times the size of
--     'Vulkan.Extensions.VK_KHR_performance_query.PerformanceCounterResultKHR'
--
-- -   #VUID-vkGetQueryPoolResults-firstQuery-00816# The sum of
--     @firstQuery@ and @queryCount@ /must/ be less than or equal to the
--     number of queries in @queryPool@
--
-- -   #VUID-vkGetQueryPoolResults-dataSize-00817# @dataSize@ /must/ be
--     large enough to contain the result of each query, as described
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-memorylayout here>
--
-- -   #VUID-vkGetQueryPoolResults-queryType-00818# If the @queryType@ used
--     to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP', @flags@ /must/
--     not contain
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT'
--
-- -   #VUID-vkGetQueryPoolResults-queryType-03230# If the @queryType@ used
--     to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     @flags@ /must/ not contain
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT',
--     @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@,
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT',
--     or 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT'
--
-- -   #VUID-vkGetQueryPoolResults-queryType-03231# If the @queryType@ used
--     to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     the @queryPool@ /must/ have been recorded once for each pass as
--     retrieved via a call to
--     'Vulkan.Extensions.VK_KHR_performance_query.getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR'
--
-- -   #VUID-vkGetQueryPoolResults-queryType-04810# If the @queryType@ used
--     to create @queryPool@ was @VK_QUERY_TYPE_RESULT_STATUS_ONLY_KHR@,
--     then @flags@ /must/ include @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@
--
-- -   #VUID-vkGetQueryPoolResults-flags-04811# If @flags@ includes
--     @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@, then it /must/ not include
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetQueryPoolResults-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkGetQueryPoolResults-queryPool-parameter# @queryPool@ /must/
--     be a valid 'Vulkan.Core10.Handles.QueryPool' handle
--
-- -   #VUID-vkGetQueryPoolResults-pData-parameter# @pData@ /must/ be a
--     valid pointer to an array of @dataSize@ bytes
--
-- -   #VUID-vkGetQueryPoolResults-flags-parameter# @flags@ /must/ be a
--     valid combination of
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlagBits' values
--
-- -   #VUID-vkGetQueryPoolResults-dataSize-arraylength# @dataSize@ /must/
--     be greater than @0@
--
-- -   #VUID-vkGetQueryPoolResults-queryPool-parent# @queryPool@ /must/
--     have been created, allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.NOT_READY'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Handles.QueryPool',
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlags'
getQueryPoolResults :: forall io
                     . (MonadIO io)
                    => -- | @device@ is the logical device that owns the query pool.
                       Device
                    -> -- | @queryPool@ is the query pool managing the queries containing the
                       -- desired results.
                       QueryPool
                    -> -- | @firstQuery@ is the initial query index.
                       ("firstQuery" ::: Word32)
                    -> -- | @queryCount@ is the number of queries to read.
                       ("queryCount" ::: Word32)
                    -> -- | @dataSize@ is the size in bytes of the buffer pointed to by @pData@.
                       ("dataSize" ::: Word64)
                    -> -- | @pData@ is a pointer to a user-allocated buffer where the results will
                       -- be written
                       ("data" ::: Ptr ())
                    -> -- | @stride@ is the stride in bytes between results for individual queries
                       -- within @pData@.
                       ("stride" ::: DeviceSize)
                    -> -- | @flags@ is a bitmask of
                       -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlagBits' specifying
                       -- how and when results are returned.
                       QueryResultFlags
                    -> io (Result)
getQueryPoolResults :: forall (io :: * -> *).
MonadIO io =>
Device
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> ("dataSize" ::: Word64)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> QueryResultFlags
-> io Result
getQueryPoolResults Device
device
                      QueryPool
queryPool
                      "firstQuery" ::: Word32
firstQuery
                      "firstQuery" ::: Word32
queryCount
                      "dataSize" ::: Word64
dataSize
                      "data" ::: Ptr ()
data'
                      "dataSize" ::: Word64
stride
                      QueryResultFlags
flags = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkGetQueryPoolResultsPtr :: FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: Word64)
   -> QueryResultFlags
   -> IO Result)
vkGetQueryPoolResultsPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> QueryPool
      -> ("firstQuery" ::: Word32)
      -> ("firstQuery" ::: Word32)
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> ("dataSize" ::: Word64)
      -> QueryResultFlags
      -> IO Result)
pVkGetQueryPoolResults (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: Word64)
   -> QueryResultFlags
   -> IO Result)
vkGetQueryPoolResultsPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetQueryPoolResults is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetQueryPoolResults' :: Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> QueryResultFlags
-> IO Result
vkGetQueryPoolResults' = FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: Word64)
   -> QueryResultFlags
   -> IO Result)
-> Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> QueryResultFlags
-> IO Result
mkVkGetQueryPoolResults FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: Word64)
   -> QueryResultFlags
   -> IO Result)
vkGetQueryPoolResultsPtr
  Result
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetQueryPoolResults" (Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> QueryResultFlags
-> IO Result
vkGetQueryPoolResults'
                                                   (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                   (QueryPool
queryPool)
                                                   ("firstQuery" ::: Word32
firstQuery)
                                                   ("firstQuery" ::: Word32
queryCount)
                                                   (("dataSize" ::: Word64) -> "dataSize" ::: CSize
CSize ("dataSize" ::: Word64
dataSize))
                                                   ("data" ::: Ptr ()
data')
                                                   ("dataSize" ::: Word64
stride)
                                                   (QueryResultFlags
flags))
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Result
r)


-- | VkQueryPoolCreateInfo - Structure specifying parameters of a newly
-- created query pool
--
-- = Description
--
-- @pipelineStatistics@ is ignored if @queryType@ is not
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS'.
--
-- == Valid Usage
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-00791# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-pipelineStatisticsQuery pipelineStatisticsQuery>
--     feature is not enabled, @queryType@ /must/ not be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS'
--
-- -   #VUID-VkQueryPoolCreateInfo-meshShaderQueries-07068# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-meshShaderQueries meshShaderQueries>
--     feature is not enabled, @queryType@ /must/ not be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MESH_PRIMITIVES_GENERATED_EXT'
--
-- -   #VUID-VkQueryPoolCreateInfo-meshShaderQueries-07069# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-meshShaderQueries meshShaderQueries>
--     feature is not enabled, and @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS',
--     @pipelineStatistics@ /must/ not contain
--     'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QUERY_PIPELINE_STATISTIC_TASK_SHADER_INVOCATIONS_BIT_EXT'
--     or
--     'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QUERY_PIPELINE_STATISTIC_MESH_SHADER_INVOCATIONS_BIT_EXT'
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-00792# If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS',
--     @pipelineStatistics@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QueryPipelineStatisticFlagBits'
--     values
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-03222# If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     the @pNext@ chain /must/ include a
--     'Vulkan.Extensions.VK_KHR_performance_query.QueryPoolPerformanceCreateInfoKHR'
--     structure
--
-- -   #VUID-VkQueryPoolCreateInfo-queryCount-02763# @queryCount@ /must/ be
--     greater than 0
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-07133# If @queryType@ is
--     @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@, then the @pNext@ chain
--     /must/ include a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoProfileInfoKHR VkVideoProfileInfoKHR>
--     structure with @videoCodecOperation@ specifying an encode operation
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-07906# If @queryType@ is
--     @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@, then the @pNext@ chain
--     /must/ include a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolVideoEncodeFeedbackCreateInfoKHR VkQueryPoolVideoEncodeFeedbackCreateInfoKHR>
--     structure
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-07907# If @queryType@ is
--     @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@, and the @pNext@ chain
--     includes a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoProfileInfoKHR VkVideoProfileInfoKHR>
--     structure and a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolVideoEncodeFeedbackCreateInfoKHR VkQueryPoolVideoEncodeFeedbackCreateInfoKHR>
--     structure, then
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolVideoEncodeFeedbackCreateInfoKHR VkQueryPoolVideoEncodeFeedbackCreateInfoKHR>::@encodeFeedbackFlags@
--     /must/ not contain any bits that are not set in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoEncodeCapabilitiesKHR VkVideoEncodeCapabilitiesKHR>::@supportedEncodeFeedbackFlags@,
--     as returned by
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkGetPhysicalDeviceVideoCapabilitiesKHR vkGetPhysicalDeviceVideoCapabilitiesKHR>
--     for the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#video-profiles video profile>
--     described by
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoProfileInfoKHR VkVideoProfileInfoKHR>
--     and its @pNext@ chain
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkQueryPoolCreateInfo-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO'
--
-- -   #VUID-VkQueryPoolCreateInfo-pNext-pNext# Each @pNext@ member of any
--     structure (including this one) in the @pNext@ chain /must/ be either
--     @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_KHR_performance_query.QueryPoolPerformanceCreateInfoKHR',
--     'Vulkan.Extensions.VK_INTEL_performance_query.QueryPoolPerformanceQueryCreateInfoINTEL',
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolVideoEncodeFeedbackCreateInfoKHR VkQueryPoolVideoEncodeFeedbackCreateInfoKHR>,
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoDecodeH264ProfileInfoKHR VkVideoDecodeH264ProfileInfoKHR>,
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoDecodeH265ProfileInfoKHR VkVideoDecodeH265ProfileInfoKHR>,
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoDecodeUsageInfoKHR VkVideoDecodeUsageInfoKHR>,
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoEncodeH264ProfileInfoEXT VkVideoEncodeH264ProfileInfoEXT>,
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoEncodeH265ProfileInfoEXT VkVideoEncodeH265ProfileInfoEXT>,
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoEncodeUsageInfoKHR VkVideoEncodeUsageInfoKHR>,
--     or
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoProfileInfoKHR VkVideoProfileInfoKHR>
--
-- -   #VUID-VkQueryPoolCreateInfo-sType-unique# The @sType@ value of each
--     struct in the @pNext@ chain /must/ be unique
--
-- -   #VUID-VkQueryPoolCreateInfo-flags-zerobitmask# @flags@ /must/ be @0@
--
-- -   #VUID-VkQueryPoolCreateInfo-queryType-parameter# @queryType@ /must/
--     be a valid 'Vulkan.Core10.Enums.QueryType.QueryType' value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QueryPipelineStatisticFlags',
-- 'Vulkan.Core10.Enums.QueryPoolCreateFlags.QueryPoolCreateFlags',
-- 'Vulkan.Core10.Enums.QueryType.QueryType',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createQueryPool'
data QueryPoolCreateInfo (es :: [Type]) = QueryPoolCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    forall (es :: [*]). QueryPoolCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    forall (es :: [*]). QueryPoolCreateInfo es -> QueryPoolCreateFlags
flags :: QueryPoolCreateFlags
  , -- | @queryType@ is a 'Vulkan.Core10.Enums.QueryType.QueryType' value
    -- specifying the type of queries managed by the pool.
    forall (es :: [*]). QueryPoolCreateInfo es -> QueryType
queryType :: QueryType
  , -- | @queryCount@ is the number of queries managed by the pool.
    forall (es :: [*]).
QueryPoolCreateInfo es -> "firstQuery" ::: Word32
queryCount :: Word32
  , -- | @pipelineStatistics@ is a bitmask of
    -- 'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QueryPipelineStatisticFlagBits'
    -- specifying which counters will be returned in queries on the new pool,
    -- as described below in
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-pipestats>.
    forall (es :: [*]).
QueryPoolCreateInfo es -> QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueryPoolCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (QueryPoolCreateInfo es)

instance Extensible QueryPoolCreateInfo where
  extensibleTypeName :: String
extensibleTypeName = String
"QueryPoolCreateInfo"
  setNext :: forall (ds :: [*]) (es :: [*]).
QueryPoolCreateInfo ds -> Chain es -> QueryPoolCreateInfo es
setNext QueryPoolCreateInfo{"firstQuery" ::: Word32
Chain ds
QueryType
QueryPoolCreateFlags
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryCount :: "firstQuery" ::: Word32
queryType :: QueryType
flags :: QueryPoolCreateFlags
next :: Chain ds
$sel:pipelineStatistics:QueryPoolCreateInfo :: forall (es :: [*]).
QueryPoolCreateInfo es -> QueryPipelineStatisticFlags
$sel:queryCount:QueryPoolCreateInfo :: forall (es :: [*]).
QueryPoolCreateInfo es -> "firstQuery" ::: Word32
$sel:queryType:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> QueryType
$sel:flags:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> QueryPoolCreateFlags
$sel:next:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> Chain es
..} Chain es
next' = QueryPoolCreateInfo{$sel:next:QueryPoolCreateInfo :: Chain es
next = Chain es
next', "firstQuery" ::: Word32
QueryType
QueryPoolCreateFlags
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryCount :: "firstQuery" ::: Word32
queryType :: QueryType
flags :: QueryPoolCreateFlags
$sel:pipelineStatistics:QueryPoolCreateInfo :: QueryPipelineStatisticFlags
$sel:queryCount:QueryPoolCreateInfo :: "firstQuery" ::: Word32
$sel:queryType:QueryPoolCreateInfo :: QueryType
$sel:flags:QueryPoolCreateInfo :: QueryPoolCreateFlags
..}
  getNext :: forall (es :: [*]). QueryPoolCreateInfo es -> Chain es
getNext QueryPoolCreateInfo{"firstQuery" ::: Word32
Chain es
QueryType
QueryPoolCreateFlags
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryCount :: "firstQuery" ::: Word32
queryType :: QueryType
flags :: QueryPoolCreateFlags
next :: Chain es
$sel:pipelineStatistics:QueryPoolCreateInfo :: forall (es :: [*]).
QueryPoolCreateInfo es -> QueryPipelineStatisticFlags
$sel:queryCount:QueryPoolCreateInfo :: forall (es :: [*]).
QueryPoolCreateInfo es -> "firstQuery" ::: Word32
$sel:queryType:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> QueryType
$sel:flags:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> QueryPoolCreateFlags
$sel:next:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> Chain es
..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends QueryPoolCreateInfo e => b) -> Maybe b
  extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends QueryPoolCreateInfo e => b) -> Maybe b
extends proxy e
_ Extends QueryPoolCreateInfo e => b
f
    | Just e :~: QueryPoolPerformanceQueryCreateInfoINTEL
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @QueryPoolPerformanceQueryCreateInfoINTEL = forall a. a -> Maybe a
Just Extends QueryPoolCreateInfo e => b
f
    | Just e :~: QueryPoolPerformanceCreateInfoKHR
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @QueryPoolPerformanceCreateInfoKHR = forall a. a -> Maybe a
Just Extends QueryPoolCreateInfo e => b
f
    | Bool
otherwise = forall a. Maybe a
Nothing

instance ( Extendss QueryPoolCreateInfo es
         , PokeChain es ) => ToCStruct (QueryPoolCreateInfo es) where
  withCStruct :: forall b.
QueryPoolCreateInfo es
-> (Ptr (QueryPoolCreateInfo es) -> IO b) -> IO b
withCStruct QueryPoolCreateInfo es
x Ptr (QueryPoolCreateInfo es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr (QueryPoolCreateInfo es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (QueryPoolCreateInfo es)
p QueryPoolCreateInfo es
x (Ptr (QueryPoolCreateInfo es) -> IO b
f Ptr (QueryPoolCreateInfo es)
p)
  pokeCStruct :: forall b.
Ptr (QueryPoolCreateInfo es)
-> QueryPoolCreateInfo es -> IO b -> IO b
pokeCStruct Ptr (QueryPoolCreateInfo es)
p QueryPoolCreateInfo{"firstQuery" ::: Word32
Chain es
QueryType
QueryPoolCreateFlags
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryCount :: "firstQuery" ::: Word32
queryType :: QueryType
flags :: QueryPoolCreateFlags
next :: Chain es
$sel:pipelineStatistics:QueryPoolCreateInfo :: forall (es :: [*]).
QueryPoolCreateInfo es -> QueryPipelineStatisticFlags
$sel:queryCount:QueryPoolCreateInfo :: forall (es :: [*]).
QueryPoolCreateInfo es -> "firstQuery" ::: Word32
$sel:queryType:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> QueryType
$sel:flags:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> QueryPoolCreateFlags
$sel:next:QueryPoolCreateInfo :: forall (es :: [*]). QueryPoolCreateInfo es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO)
    "data" ::: Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueryPoolCreateFlags)) (QueryPoolCreateFlags
flags)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr QueryType)) (QueryType
queryType)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ("firstQuery" ::: Word32
queryCount)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr QueryPipelineStatisticFlags)) (QueryPipelineStatisticFlags
pipelineStatistics)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr (QueryPoolCreateInfo es) -> IO b -> IO b
pokeZeroCStruct Ptr (QueryPoolCreateInfo es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO)
    "data" ::: Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr QueryType)) (forall a. Zero a => a
zero)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance ( Extendss QueryPoolCreateInfo es
         , PeekChain es ) => FromCStruct (QueryPoolCreateInfo es) where
  peekCStruct :: Ptr (QueryPoolCreateInfo es) -> IO (QueryPoolCreateInfo es)
peekCStruct Ptr (QueryPoolCreateInfo es)
p = do
    "data" ::: Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
    Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr "data" ::: Ptr ()
pNext)
    QueryPoolCreateFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @QueryPoolCreateFlags ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueryPoolCreateFlags))
    QueryType
queryType <- forall a. Storable a => Ptr a -> IO a
peek @QueryType ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr QueryType))
    "firstQuery" ::: Word32
queryCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
    QueryPipelineStatisticFlags
pipelineStatistics <- forall a. Storable a => Ptr a -> IO a
peek @QueryPipelineStatisticFlags ((Ptr (QueryPoolCreateInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr QueryPipelineStatisticFlags))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es
-> QueryPoolCreateFlags
-> QueryType
-> ("firstQuery" ::: Word32)
-> QueryPipelineStatisticFlags
-> QueryPoolCreateInfo es
QueryPoolCreateInfo
             Chain es
next QueryPoolCreateFlags
flags QueryType
queryType "firstQuery" ::: Word32
queryCount QueryPipelineStatisticFlags
pipelineStatistics

instance es ~ '[] => Zero (QueryPoolCreateInfo es) where
  zero :: QueryPoolCreateInfo es
zero = forall (es :: [*]).
Chain es
-> QueryPoolCreateFlags
-> QueryType
-> ("firstQuery" ::: Word32)
-> QueryPipelineStatisticFlags
-> QueryPoolCreateInfo es
QueryPoolCreateInfo
           ()
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero