{-# language CPP #-}
-- No documentation found for Chapter "Promoted_From_VK_EXT_host_query_reset"
module Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset  ( resetQueryPool
                                                            , PhysicalDeviceHostQueryResetFeatures(..)
                                                            , StructureType(..)
                                                            ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
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.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkResetQueryPool))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Handles (QueryPool)
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkResetQueryPool
  :: FunPtr (Ptr Device_T -> QueryPool -> Word32 -> Word32 -> IO ()) -> Ptr Device_T -> QueryPool -> Word32 -> Word32 -> IO ()

-- | vkResetQueryPool - Reset queries in a query pool
--
-- = Description
--
-- This command sets the status of query indices [@firstQuery@,
-- @firstQuery@ + @queryCount@ - 1] to unavailable.
--
-- If @queryPool@ is
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' this
-- command sets the status of query indices [@firstQuery@, @firstQuery@ +
-- @queryCount@ - 1] to unavailable for each pass.
--
-- == Valid Usage
--
-- -   #VUID-vkResetQueryPool-None-02665# The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-hostQueryReset hostQueryReset>
--     feature /must/ be enabled
--
-- -   #VUID-vkResetQueryPool-firstQuery-02666# @firstQuery@ /must/ be less
--     than the number of queries in @queryPool@
--
-- -   #VUID-vkResetQueryPool-firstQuery-02667# The sum of @firstQuery@ and
--     @queryCount@ /must/ be less than or equal to the number of queries
--     in @queryPool@
--
-- -   #VUID-vkResetQueryPool-firstQuery-02741# Submitted commands that
--     refer to the range specified by @firstQuery@ and @queryCount@ in
--     @queryPool@ /must/ have completed execution
--
-- -   #VUID-vkResetQueryPool-firstQuery-02742# The range of queries
--     specified by @firstQuery@ and @queryCount@ in @queryPool@ /must/ not
--     be in use by calls to 'Vulkan.Core10.Query.getQueryPoolResults' or
--     'resetQueryPool' in other threads
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkResetQueryPool-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkResetQueryPool-queryPool-parameter# @queryPool@ /must/ be a
--     valid 'Vulkan.Core10.Handles.QueryPool' handle
--
-- -   #VUID-vkResetQueryPool-queryPool-parent# @queryPool@ /must/ have
--     been created, allocated, or retrieved from @device@
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_host_query_reset VK_EXT_host_query_reset>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.QueryPool'
resetQueryPool :: forall io
                . (MonadIO io)
               => -- | @device@ is the logical device that owns the query pool.
                  Device
               -> -- | @queryPool@ is the handle of the query pool managing the queries being
                  -- reset.
                  QueryPool
               -> -- | @firstQuery@ is the initial query index to reset.
                  ("firstQuery" ::: Word32)
               -> -- | @queryCount@ is the number of queries to reset.
                  ("queryCount" ::: Word32)
               -> io ()
resetQueryPool :: Device
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> io ()
resetQueryPool Device
device QueryPool
queryPool "firstQuery" ::: Word32
firstQuery "firstQuery" ::: Word32
queryCount = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkResetQueryPoolPtr :: FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> IO ())
vkResetQueryPoolPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> QueryPool
      -> ("firstQuery" ::: Word32)
      -> ("firstQuery" ::: Word32)
      -> IO ())
pVkResetQueryPool (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> IO ())
vkResetQueryPoolPtr FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> QueryPool
      -> ("firstQuery" ::: Word32)
      -> ("firstQuery" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> 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 String
"" String
"The function pointer for vkResetQueryPool is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkResetQueryPool' :: Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> IO ()
vkResetQueryPool' = FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> IO ())
-> Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> IO ()
mkVkResetQueryPool FunPtr
  (Ptr Device_T
   -> QueryPool
   -> ("firstQuery" ::: Word32)
   -> ("firstQuery" ::: Word32)
   -> IO ())
vkResetQueryPoolPtr
  String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkResetQueryPool" (Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> IO ()
vkResetQueryPool' (Device -> Ptr Device_T
deviceHandle (Device
device)) (QueryPool
queryPool) ("firstQuery" ::: Word32
firstQuery) ("firstQuery" ::: Word32
queryCount))
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDeviceHostQueryResetFeatures - Structure describing whether
-- queries can be reset from the host
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceHostQueryResetFeatures' structure is included in
-- the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceHostQueryResetFeatures' /can/ also be used in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_host_query_reset VK_EXT_host_query_reset>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceHostQueryResetFeatures = PhysicalDeviceHostQueryResetFeatures
  { -- | #extension-features-hostQueryReset# @hostQueryReset@ indicates that the
    -- implementation supports resetting queries from the host with
    -- 'resetQueryPool'.
    PhysicalDeviceHostQueryResetFeatures -> Bool
hostQueryReset :: Bool }
  deriving (Typeable, PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> Bool
(PhysicalDeviceHostQueryResetFeatures
 -> PhysicalDeviceHostQueryResetFeatures -> Bool)
-> (PhysicalDeviceHostQueryResetFeatures
    -> PhysicalDeviceHostQueryResetFeatures -> Bool)
-> Eq PhysicalDeviceHostQueryResetFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> Bool
$c/= :: PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> Bool
== :: PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> Bool
$c== :: PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceHostQueryResetFeatures)
#endif
deriving instance Show PhysicalDeviceHostQueryResetFeatures

instance ToCStruct PhysicalDeviceHostQueryResetFeatures where
  withCStruct :: PhysicalDeviceHostQueryResetFeatures
-> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceHostQueryResetFeatures
x Ptr PhysicalDeviceHostQueryResetFeatures -> IO b
f = Int -> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b)
-> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceHostQueryResetFeatures
p -> Ptr PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceHostQueryResetFeatures
p PhysicalDeviceHostQueryResetFeatures
x (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b
f Ptr PhysicalDeviceHostQueryResetFeatures
p)
  pokeCStruct :: Ptr PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceHostQueryResetFeatures
p PhysicalDeviceHostQueryResetFeatures{Bool
hostQueryReset :: Bool
$sel:hostQueryReset:PhysicalDeviceHostQueryResetFeatures :: PhysicalDeviceHostQueryResetFeatures -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
hostQueryReset))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceHostQueryResetFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceHostQueryResetFeatures
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceHostQueryResetFeatures where
  peekCStruct :: Ptr PhysicalDeviceHostQueryResetFeatures
-> IO PhysicalDeviceHostQueryResetFeatures
peekCStruct Ptr PhysicalDeviceHostQueryResetFeatures
p = do
    Bool32
hostQueryReset <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceHostQueryResetFeatures
p Ptr PhysicalDeviceHostQueryResetFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    PhysicalDeviceHostQueryResetFeatures
-> IO PhysicalDeviceHostQueryResetFeatures
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceHostQueryResetFeatures
 -> IO PhysicalDeviceHostQueryResetFeatures)
-> PhysicalDeviceHostQueryResetFeatures
-> IO PhysicalDeviceHostQueryResetFeatures
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceHostQueryResetFeatures
PhysicalDeviceHostQueryResetFeatures
             (Bool32 -> Bool
bool32ToBool Bool32
hostQueryReset)

instance Storable PhysicalDeviceHostQueryResetFeatures where
  sizeOf :: PhysicalDeviceHostQueryResetFeatures -> Int
sizeOf ~PhysicalDeviceHostQueryResetFeatures
_ = Int
24
  alignment :: PhysicalDeviceHostQueryResetFeatures -> Int
alignment ~PhysicalDeviceHostQueryResetFeatures
_ = Int
8
  peek :: Ptr PhysicalDeviceHostQueryResetFeatures
-> IO PhysicalDeviceHostQueryResetFeatures
peek = Ptr PhysicalDeviceHostQueryResetFeatures
-> IO PhysicalDeviceHostQueryResetFeatures
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> IO ()
poke Ptr PhysicalDeviceHostQueryResetFeatures
ptr PhysicalDeviceHostQueryResetFeatures
poked = Ptr PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceHostQueryResetFeatures
ptr PhysicalDeviceHostQueryResetFeatures
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceHostQueryResetFeatures where
  zero :: PhysicalDeviceHostQueryResetFeatures
zero = Bool -> PhysicalDeviceHostQueryResetFeatures
PhysicalDeviceHostQueryResetFeatures
           Bool
forall a. Zero a => a
zero