{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset ( resetQueryPool
, PhysicalDeviceHostQueryResetFeatures(..)
, StructureType(..)
) where
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.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.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkResetQueryPool))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (QueryPool)
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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 :: Device
-> QueryPool
-> ("firstQuery" ::: Word32)
-> ("firstQuery" ::: Word32)
-> io ()
resetQueryPool device :: Device
device queryPool :: QueryPool
queryPool firstQuery :: "firstQuery" ::: Word32
firstQuery queryCount :: "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 (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)
-> 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 "" "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
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
$ ()
data PhysicalDeviceHostQueryResetFeatures = PhysicalDeviceHostQueryResetFeatures
{
PhysicalDeviceHostQueryResetFeatures -> Bool
hostQueryReset :: Bool }
deriving (Typeable)
deriving instance Show PhysicalDeviceHostQueryResetFeatures
instance ToCStruct PhysicalDeviceHostQueryResetFeatures where
withCStruct :: PhysicalDeviceHostQueryResetFeatures
-> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b
withCStruct x :: PhysicalDeviceHostQueryResetFeatures
x f :: Ptr PhysicalDeviceHostQueryResetFeatures -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b)
-> (Ptr PhysicalDeviceHostQueryResetFeatures -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 p :: Ptr PhysicalDeviceHostQueryResetFeatures
p PhysicalDeviceHostQueryResetFeatures{..} f :: 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` 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` 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` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
hostQueryReset))
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDeviceHostQueryResetFeatures -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceHostQueryResetFeatures
p f :: 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` 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` 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` 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 p :: 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` 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
_ = 24
alignment :: PhysicalDeviceHostQueryResetFeatures -> Int
alignment ~PhysicalDeviceHostQueryResetFeatures
_ = 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 :: Ptr PhysicalDeviceHostQueryResetFeatures
ptr poked :: 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