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

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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 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.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 (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
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.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
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)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'QueryPoolCreateInfo' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @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
--
-- '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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                   -- chapter.
                   ("allocator" ::: Maybe AllocationCallbacks)
                -> io (QueryPool)
createQueryPool :: Device
-> QueryPoolCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io QueryPool
createQueryPool device :: Device
device createInfo :: QueryPoolCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO QueryPool -> io QueryPool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO QueryPool -> io QueryPool)
-> (ContT QueryPool IO QueryPool -> IO QueryPool)
-> ContT QueryPool IO QueryPool
-> io QueryPool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT QueryPool IO QueryPool -> IO QueryPool
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT QueryPool IO QueryPool -> io QueryPool)
-> ContT QueryPool IO QueryPool -> io QueryPool
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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT QueryPool IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT QueryPool IO ()) -> IO () -> ContT QueryPool IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
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 FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pQueryPool" ::: Ptr QueryPool)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pQueryPool" ::: Ptr QueryPool)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pQueryPool" ::: Ptr QueryPool)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateQueryPool is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((Ptr (QueryPoolCreateInfo a) -> IO QueryPool) -> IO QueryPool)
-> ContT QueryPool IO (Ptr (QueryPoolCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (QueryPoolCreateInfo a) -> IO QueryPool) -> IO QueryPool)
 -> ContT QueryPool IO (Ptr (QueryPoolCreateInfo a)))
-> ((Ptr (QueryPoolCreateInfo a) -> IO QueryPool) -> IO QueryPool)
-> ContT QueryPool IO (Ptr (QueryPoolCreateInfo a))
forall a b. (a -> b) -> a -> b
$ QueryPoolCreateInfo a
-> (Ptr (QueryPoolCreateInfo a) -> IO QueryPool) -> IO QueryPool
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
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT QueryPool IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO QueryPool)
 -> IO QueryPool)
-> ContT QueryPool IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO QueryPool)
  -> IO QueryPool)
 -> ContT QueryPool IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO QueryPool)
    -> IO QueryPool)
-> ContT QueryPool IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO QueryPool)
-> IO QueryPool
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pQueryPool" ::: Ptr QueryPool
pPQueryPool <- ((("pQueryPool" ::: Ptr QueryPool) -> IO QueryPool)
 -> IO QueryPool)
-> ContT QueryPool IO ("pQueryPool" ::: Ptr QueryPool)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pQueryPool" ::: Ptr QueryPool) -> IO QueryPool)
  -> IO QueryPool)
 -> ContT QueryPool IO ("pQueryPool" ::: Ptr QueryPool))
-> ((("pQueryPool" ::: Ptr QueryPool) -> IO QueryPool)
    -> IO QueryPool)
-> ContT QueryPool IO ("pQueryPool" ::: Ptr QueryPool)
forall a b. (a -> b) -> a -> b
$ IO ("pQueryPool" ::: Ptr QueryPool)
-> (("pQueryPool" ::: Ptr QueryPool) -> IO ())
-> (("pQueryPool" ::: Ptr QueryPool) -> IO QueryPool)
-> IO QueryPool
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pQueryPool" ::: Ptr QueryPool)
forall a. Int -> IO (Ptr a)
callocBytes @QueryPool 8) ("pQueryPool" ::: Ptr QueryPool) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT QueryPool IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT QueryPool IO Result)
-> IO Result -> ContT QueryPool IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pQueryPool" ::: Ptr QueryPool)
-> IO Result
vkCreateQueryPool' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (QueryPoolCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct QueryPoolCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (QueryPoolCreateInfo a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pQueryPool" ::: Ptr QueryPool
pPQueryPool)
  IO () -> ContT QueryPool IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT QueryPool IO ()) -> IO () -> ContT QueryPool IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  QueryPool
pQueryPool <- IO QueryPool -> ContT QueryPool IO QueryPool
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO QueryPool -> ContT QueryPool IO QueryPool)
-> IO QueryPool -> ContT QueryPool IO QueryPool
forall a b. (a -> b) -> a -> b
$ ("pQueryPool" ::: Ptr QueryPool) -> IO QueryPool
forall a. Storable a => Ptr a -> IO a
peek @QueryPool "pQueryPool" ::: Ptr QueryPool
pPQueryPool
  QueryPool -> ContT QueryPool IO QueryPool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (QueryPool -> ContT QueryPool IO QueryPool)
-> QueryPool -> ContT QueryPool IO QueryPool
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 first argument.
-- To just extract the pair pass '(,)' as the first 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 :: Device
-> QueryPoolCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io QueryPool -> (QueryPool -> io ()) -> r)
-> r
withQueryPool device :: Device
device pCreateInfo :: QueryPoolCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io QueryPool -> (QueryPool -> io ()) -> r
b =
  io QueryPool -> (QueryPool -> io ()) -> r
b (Device
-> QueryPoolCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io QueryPool
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) -> Device
-> QueryPool
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
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
--
-- -   All submitted commands that refer to @queryPool@ /must/ have
--     completed execution
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @queryPool@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @queryPool@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @queryPool@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.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
--
-- '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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                    -- chapter.
                    ("allocator" ::: Maybe AllocationCallbacks)
                 -> io ()
destroyQueryPool :: Device
-> QueryPool
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyQueryPool device :: Device
device queryPool :: QueryPool
queryPool allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyQueryPoolPtr FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> QueryPool
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyQueryPool is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> QueryPool -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyQueryPool' (Device -> Ptr Device_T
deviceHandle (Device
device)) (QueryPool
queryPool) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
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
--
-- 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
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-wait-bit-not-set below>.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is not
-- set and the result overflows a 32-bit value, the value /may/ either wrap
-- or saturate. Similarly, if
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set and
-- the result overflows a 64-bit value, the value /may/ either wrap or
-- saturate.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.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
-- 'Vulkan.Core10.Enums.Result.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 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' and
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.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 'Vulkan.Core10.Enums.Result.NOT_READY'.
-- However, availability state is still written to @pData@ for those
-- queries if
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
-- is set.
--
-- 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.
--
-- 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 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT' is
-- set, 'Vulkan.Core10.Enums.QueryResultFlagBits.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
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.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
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.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@
--
-- -   If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is
--     not set in @flags@, then @pData@ and @stride@ /must/ be multiples of
--     @4@
--
-- -   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@
--
-- -   If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is
--     set in @flags@ then @pData@ and @stride@ /must/ be multiples of @8@
--
-- -   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'
--
-- -   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
--     'Vulkan.Extensions.VK_KHR_performance_query.QueryPoolPerformanceCreateInfoKHR'::@counterIndexCount@
--     used to create @queryPool@ times the size of
--     'Vulkan.Extensions.VK_KHR_performance_query.PerformanceCounterResultKHR'.
--
-- -   The sum of @firstQuery@ and @queryCount@ /must/ be less than or
--     equal to the number of queries in @queryPool@
--
-- -   @dataSize@ /must/ be large enough to contain the result of each
--     query, as described
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-memorylayout here>
--
-- -   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'
--
-- -   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',
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT'
--     or 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT'
--
-- -   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'
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     handle
--
-- -   @pData@ /must/ be a valid pointer to an array of @dataSize@ bytes
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlagBits' values
--
-- -   @dataSize@ /must/ be greater than @0@
--
-- -   @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
--
-- '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 :: Device
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> ("dataSize" ::: Word64)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> QueryResultFlags
-> io Result
getQueryPoolResults device :: Device
device queryPool :: QueryPool
queryPool firstQuery :: "firstQuery" ::: Word32
firstQuery queryCount :: "firstQuery" ::: Word32
queryCount dataSize :: "dataSize" ::: Word64
dataSize data' :: "data" ::: Ptr ()
data' stride :: "dataSize" ::: Word64
stride flags :: QueryResultFlags
flags = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result) -> IO Result -> io Result
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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
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 FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: Word64)
   -> QueryResultFlags
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> QueryPool
      -> ("firstQuery" ::: Word32)
      -> ("firstQuery" ::: Word32)
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> ("dataSize" ::: Word64)
      -> QueryResultFlags
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: Word64)
   -> QueryResultFlags
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetQueryPoolResults is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- 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)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> IO Result) -> Result -> IO Result
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
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineStatisticsQuery pipeline statistics queries>
--     feature is not enabled, @queryType@ /must/ not be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS'
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS',
--     @pipelineStatistics@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QueryPipelineStatisticFlagBits'
--     values
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     the @pNext@ chain /must/ include a structure of type
--     'Vulkan.Extensions.VK_KHR_performance_query.QueryPoolPerformanceCreateInfoKHR'
--
-- -   @queryCount@ /must/ be greater than 0
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO'
--
-- -   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'
--     or
--     'Vulkan.Extensions.VK_INTEL_performance_query.QueryPoolPerformanceQueryCreateInfoINTEL'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- -   @queryType@ /must/ be a valid
--     'Vulkan.Core10.Enums.QueryType.QueryType' value
--
-- = See Also
--
-- '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.
    QueryPoolCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    QueryPoolCreateInfo es -> QueryPoolCreateFlags
flags :: QueryPoolCreateFlags
  , -- | @queryType@ is a 'Vulkan.Core10.Enums.QueryType.QueryType' value
    -- specifying the type of queries managed by the pool.
    QueryPoolCreateInfo es -> QueryType
queryType :: QueryType
  , -- | @queryCount@ is the number of queries managed by the pool.
    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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-pipestats>.
    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
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO
  setNext :: QueryPoolCreateInfo ds -> Chain es -> QueryPoolCreateInfo es
setNext x :: QueryPoolCreateInfo ds
x next :: Chain es
next = QueryPoolCreateInfo ds
x{$sel:next:QueryPoolCreateInfo :: Chain es
next = Chain es
next}
  getNext :: QueryPoolCreateInfo es -> Chain es
getNext QueryPoolCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends QueryPoolCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends QueryPoolCreateInfo e => b) -> Maybe b
extends _ f :: Extends QueryPoolCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable QueryPoolPerformanceQueryCreateInfoINTEL) =>
Maybe (e :~: QueryPoolPerformanceQueryCreateInfoINTEL)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @QueryPoolPerformanceQueryCreateInfoINTEL = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends QueryPoolCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable QueryPoolPerformanceCreateInfoKHR) =>
Maybe (e :~: QueryPoolPerformanceCreateInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @QueryPoolPerformanceCreateInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends QueryPoolCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

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