{-# language CPP #-}
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 ()
resetQueryPool :: forall io
. (MonadIO io)
=>
Device
->
QueryPool
->
("firstQuery" ::: Word32)
->
("queryCount" ::: Word32)
-> io ()
resetQueryPool :: forall (io :: * -> *).
MonadIO io =>
Device
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> io ()
resetQueryPool Device
device QueryPool
queryPool "firstQuery" ::: Word32
firstQuery "firstQuery" ::: Word32
queryCount = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> IO ())
vkResetQueryPoolPtr 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 vkResetQueryPool is null" forall a. Maybe a
Nothing 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
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))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
data PhysicalDeviceHostQueryResetFeatures = PhysicalDeviceHostQueryResetFeatures
{
PhysicalDeviceHostQueryResetFeatures -> Bool
hostQueryReset :: Bool }
deriving (Typeable, PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> Bool
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 :: forall b.
PhysicalDeviceHostQueryResetFeatures
-> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceHostQueryResetFeatures
x Ptr PhysicalDeviceHostQueryResetFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceHostQueryResetFeatures
p -> 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 :: forall b.
Ptr PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceHostQueryResetFeatures
p PhysicalDeviceHostQueryResetFeatures{Bool
hostQueryReset :: Bool
$sel:hostQueryReset:PhysicalDeviceHostQueryResetFeatures :: PhysicalDeviceHostQueryResetFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p 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 :: forall b. Ptr PhysicalDeviceHostQueryResetFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceHostQueryResetFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceHostQueryResetFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (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 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceHostQueryResetFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceHostQueryResetFeatures
-> PhysicalDeviceHostQueryResetFeatures -> IO ()
poke Ptr PhysicalDeviceHostQueryResetFeatures
ptr PhysicalDeviceHostQueryResetFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceHostQueryResetFeatures
ptr PhysicalDeviceHostQueryResetFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceHostQueryResetFeatures where
zero :: PhysicalDeviceHostQueryResetFeatures
zero = Bool -> PhysicalDeviceHostQueryResetFeatures
PhysicalDeviceHostQueryResetFeatures
forall a. Zero a => a
zero