{-# language CPP #-}
module Vulkan.Extensions.VK_NV_device_generated_commands_compute ( cmdUpdatePipelineIndirectBufferNV
, getPipelineIndirectMemoryRequirementsNV
, getPipelineIndirectDeviceAddressNV
, ComputePipelineIndirectBufferInfoNV(..)
, PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV(..)
, PipelineIndirectDeviceAddressInfoNV(..)
, BindPipelineIndirectCommandNV(..)
, NV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION
, pattern NV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION
, NV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME
, pattern NV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME
, IndirectCommandsTokenTypeNV(..)
) 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 Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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.String (IsString)
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.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Pipeline (ComputePipelineCreateInfo)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Core10.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkCmdUpdatePipelineIndirectBufferNV))
import Vulkan.Dynamic (DeviceCmds(pVkGetPipelineIndirectDeviceAddressNV))
import Vulkan.Dynamic (DeviceCmds(pVkGetPipelineIndirectMemoryRequirementsNV))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2 (MemoryRequirements2)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.Core10.Handles (Pipeline)
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMPUTE_PIPELINE_INDIRECT_BUFFER_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_COMPUTE_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_INDIRECT_DEVICE_ADDRESS_INFO_NV))
import Vulkan.Extensions.VK_NV_device_generated_commands (IndirectCommandsTokenTypeNV(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdUpdatePipelineIndirectBufferNV
:: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
cmdUpdatePipelineIndirectBufferNV :: forall io
. (MonadIO io)
=>
CommandBuffer
->
PipelineBindPoint
->
Pipeline
-> io ()
cmdUpdatePipelineIndirectBufferNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> PipelineBindPoint -> Pipeline -> io ()
cmdUpdatePipelineIndirectBufferNV CommandBuffer
commandBuffer
PipelineBindPoint
pipelineBindPoint
Pipeline
pipeline = IO () -> io ()
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkCmdUpdatePipelineIndirectBufferNVPtr :: FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
vkCmdUpdatePipelineIndirectBufferNVPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
pVkCmdUpdatePipelineIndirectBufferNV (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
vkCmdUpdatePipelineIndirectBufferNVPtr FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
-> FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> 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 vkCmdUpdatePipelineIndirectBufferNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCmdUpdatePipelineIndirectBufferNV' :: Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
vkCmdUpdatePipelineIndirectBufferNV' = FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
-> Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
mkVkCmdUpdatePipelineIndirectBufferNV FunPtr
(Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
vkCmdUpdatePipelineIndirectBufferNVPtr
String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdUpdatePipelineIndirectBufferNV" (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
vkCmdUpdatePipelineIndirectBufferNV'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
(PipelineBindPoint
pipelineBindPoint)
(Pipeline
pipeline))
() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPipelineIndirectMemoryRequirementsNV
:: FunPtr (Ptr Device_T -> Ptr (SomeStruct ComputePipelineCreateInfo) -> Ptr (SomeStruct MemoryRequirements2) -> IO ()) -> Ptr Device_T -> Ptr (SomeStruct ComputePipelineCreateInfo) -> Ptr (SomeStruct MemoryRequirements2) -> IO ()
getPipelineIndirectMemoryRequirementsNV :: forall a b io
. ( Extendss ComputePipelineCreateInfo a
, PokeChain a
, Extendss MemoryRequirements2 b
, PokeChain b
, PeekChain b
, MonadIO io )
=>
Device
->
(ComputePipelineCreateInfo a)
-> io (MemoryRequirements2 b)
getPipelineIndirectMemoryRequirementsNV :: forall (a :: [*]) (b :: [*]) (io :: * -> *).
(Extendss ComputePipelineCreateInfo a, PokeChain a,
Extendss MemoryRequirements2 b, PokeChain b, PeekChain b,
MonadIO io) =>
Device -> ComputePipelineCreateInfo a -> io (MemoryRequirements2 b)
getPipelineIndirectMemoryRequirementsNV Device
device
ComputePipelineCreateInfo a
createInfo = IO (MemoryRequirements2 b) -> io (MemoryRequirements2 b)
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (MemoryRequirements2 b) -> io (MemoryRequirements2 b))
-> (ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
-> IO (MemoryRequirements2 b))
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
-> io (MemoryRequirements2 b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
-> IO (MemoryRequirements2 b)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
-> io (MemoryRequirements2 b))
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
-> io (MemoryRequirements2 b)
forall a b. (a -> b) -> a -> b
$ do
let vkGetPipelineIndirectMemoryRequirementsNVPtr :: FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
vkGetPipelineIndirectMemoryRequirementsNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
pVkGetPipelineIndirectMemoryRequirementsNV (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
IO () -> ContT (MemoryRequirements2 b) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (MemoryRequirements2 b) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (MemoryRequirements2 b) IO ())
-> IO () -> ContT (MemoryRequirements2 b) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
vkGetPipelineIndirectMemoryRequirementsNVPtr FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
-> FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> 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 vkGetPipelineIndirectMemoryRequirementsNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPipelineIndirectMemoryRequirementsNV' :: Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ()
vkGetPipelineIndirectMemoryRequirementsNV' = FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
-> Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ()
mkVkGetPipelineIndirectMemoryRequirementsNV FunPtr
(Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ())
vkGetPipelineIndirectMemoryRequirementsNVPtr
Ptr (ComputePipelineCreateInfo a)
pCreateInfo <- ((Ptr (ComputePipelineCreateInfo a) -> IO (MemoryRequirements2 b))
-> IO (MemoryRequirements2 b))
-> ContT
(MemoryRequirements2 b) IO (Ptr (ComputePipelineCreateInfo a))
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ComputePipelineCreateInfo a) -> IO (MemoryRequirements2 b))
-> IO (MemoryRequirements2 b))
-> ContT
(MemoryRequirements2 b) IO (Ptr (ComputePipelineCreateInfo a)))
-> ((Ptr (ComputePipelineCreateInfo a)
-> IO (MemoryRequirements2 b))
-> IO (MemoryRequirements2 b))
-> ContT
(MemoryRequirements2 b) IO (Ptr (ComputePipelineCreateInfo a))
forall a b. (a -> b) -> a -> b
$ ComputePipelineCreateInfo a
-> (Ptr (ComputePipelineCreateInfo a)
-> IO (MemoryRequirements2 b))
-> IO (MemoryRequirements2 b)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
forall b.
ComputePipelineCreateInfo a
-> (Ptr (ComputePipelineCreateInfo a) -> IO b) -> IO b
withCStruct (ComputePipelineCreateInfo a
createInfo)
Ptr (MemoryRequirements2 b)
pPMemoryRequirements <- ((Ptr (MemoryRequirements2 b) -> IO (MemoryRequirements2 b))
-> IO (MemoryRequirements2 b))
-> ContT (MemoryRequirements2 b) IO (Ptr (MemoryRequirements2 b))
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(MemoryRequirements2 _))
IO () -> ContT (MemoryRequirements2 b) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (MemoryRequirements2 b) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (MemoryRequirements2 b) IO ())
-> IO () -> ContT (MemoryRequirements2 b) IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPipelineIndirectMemoryRequirementsNV" (Ptr Device_T
-> Ptr (SomeStruct ComputePipelineCreateInfo)
-> Ptr (SomeStruct MemoryRequirements2)
-> IO ()
vkGetPipelineIndirectMemoryRequirementsNV'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(Ptr (ComputePipelineCreateInfo a)
-> Ptr (SomeStruct ComputePipelineCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (ComputePipelineCreateInfo a)
pCreateInfo)
(Ptr (MemoryRequirements2 b) -> Ptr (SomeStruct MemoryRequirements2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (MemoryRequirements2 b)
pPMemoryRequirements)))
MemoryRequirements2 b
pMemoryRequirements <- IO (MemoryRequirements2 b)
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (MemoryRequirements2 b) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (MemoryRequirements2 b)
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b))
-> IO (MemoryRequirements2 b)
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(MemoryRequirements2 _) Ptr (MemoryRequirements2 b)
pPMemoryRequirements
MemoryRequirements2 b
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
forall a. a -> ContT (MemoryRequirements2 b) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryRequirements2 b
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b))
-> MemoryRequirements2 b
-> ContT (MemoryRequirements2 b) IO (MemoryRequirements2 b)
forall a b. (a -> b) -> a -> b
$ (MemoryRequirements2 b
pMemoryRequirements)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPipelineIndirectDeviceAddressNV
:: FunPtr (Ptr Device_T -> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress) -> Ptr Device_T -> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress
getPipelineIndirectDeviceAddressNV :: forall io
. (MonadIO io)
=>
Device
->
PipelineIndirectDeviceAddressInfoNV
-> io (DeviceAddress)
getPipelineIndirectDeviceAddressNV :: forall (io :: * -> *).
MonadIO io =>
Device -> PipelineIndirectDeviceAddressInfoNV -> io DeviceAddress
getPipelineIndirectDeviceAddressNV Device
device PipelineIndirectDeviceAddressInfoNV
info = IO DeviceAddress -> io DeviceAddress
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceAddress -> io DeviceAddress)
-> (ContT DeviceAddress IO DeviceAddress -> IO DeviceAddress)
-> ContT DeviceAddress IO DeviceAddress
-> io DeviceAddress
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT DeviceAddress IO DeviceAddress -> IO DeviceAddress
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT DeviceAddress IO DeviceAddress -> io DeviceAddress)
-> ContT DeviceAddress IO DeviceAddress -> io DeviceAddress
forall a b. (a -> b) -> a -> b
$ do
let vkGetPipelineIndirectDeviceAddressNVPtr :: FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
vkGetPipelineIndirectDeviceAddressNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
pVkGetPipelineIndirectDeviceAddressNV (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
IO () -> ContT DeviceAddress IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT DeviceAddress m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeviceAddress IO ())
-> IO () -> ContT DeviceAddress IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
vkGetPipelineIndirectDeviceAddressNVPtr FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
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 vkGetPipelineIndirectDeviceAddressNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPipelineIndirectDeviceAddressNV' :: Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress
vkGetPipelineIndirectDeviceAddressNV' = FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV
-> IO DeviceAddress
mkVkGetPipelineIndirectDeviceAddressNV FunPtr
(Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
vkGetPipelineIndirectDeviceAddressNVPtr
Ptr PipelineIndirectDeviceAddressInfoNV
pInfo <- ((Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> IO DeviceAddress)
-> ContT DeviceAddress IO (Ptr PipelineIndirectDeviceAddressInfoNV)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> IO DeviceAddress)
-> ContT
DeviceAddress IO (Ptr PipelineIndirectDeviceAddressInfoNV))
-> ((Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> IO DeviceAddress)
-> ContT DeviceAddress IO (Ptr PipelineIndirectDeviceAddressInfoNV)
forall a b. (a -> b) -> a -> b
$ PipelineIndirectDeviceAddressInfoNV
-> (Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress)
-> IO DeviceAddress
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
forall b.
PipelineIndirectDeviceAddressInfoNV
-> (Ptr PipelineIndirectDeviceAddressInfoNV -> IO b) -> IO b
withCStruct (PipelineIndirectDeviceAddressInfoNV
info)
DeviceAddress
r <- IO DeviceAddress -> ContT DeviceAddress IO DeviceAddress
forall (m :: * -> *) a. Monad m => m a -> ContT DeviceAddress m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DeviceAddress -> ContT DeviceAddress IO DeviceAddress)
-> IO DeviceAddress -> ContT DeviceAddress IO DeviceAddress
forall a b. (a -> b) -> a -> b
$ String -> IO DeviceAddress -> IO DeviceAddress
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPipelineIndirectDeviceAddressNV" (Ptr Device_T
-> Ptr PipelineIndirectDeviceAddressInfoNV -> IO DeviceAddress
vkGetPipelineIndirectDeviceAddressNV'
(Device -> Ptr Device_T
deviceHandle (Device
device))
Ptr PipelineIndirectDeviceAddressInfoNV
pInfo)
DeviceAddress -> ContT DeviceAddress IO DeviceAddress
forall a. a -> ContT DeviceAddress IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceAddress -> ContT DeviceAddress IO DeviceAddress)
-> DeviceAddress -> ContT DeviceAddress IO DeviceAddress
forall a b. (a -> b) -> a -> b
$ (DeviceAddress
r)
data ComputePipelineIndirectBufferInfoNV = ComputePipelineIndirectBufferInfoNV
{
ComputePipelineIndirectBufferInfoNV -> DeviceAddress
deviceAddress :: DeviceAddress
,
ComputePipelineIndirectBufferInfoNV -> DeviceAddress
size :: DeviceSize
,
ComputePipelineIndirectBufferInfoNV -> DeviceAddress
pipelineDeviceAddressCaptureReplay :: DeviceAddress
}
deriving (Typeable, ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool
(ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool)
-> (ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool)
-> Eq ComputePipelineIndirectBufferInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool
== :: ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool
$c/= :: ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool
/= :: ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ComputePipelineIndirectBufferInfoNV)
#endif
deriving instance Show ComputePipelineIndirectBufferInfoNV
instance ToCStruct ComputePipelineIndirectBufferInfoNV where
withCStruct :: forall b.
ComputePipelineIndirectBufferInfoNV
-> (Ptr ComputePipelineIndirectBufferInfoNV -> IO b) -> IO b
withCStruct ComputePipelineIndirectBufferInfoNV
x Ptr ComputePipelineIndirectBufferInfoNV -> IO b
f = Int -> (Ptr ComputePipelineIndirectBufferInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr ComputePipelineIndirectBufferInfoNV -> IO b) -> IO b)
-> (Ptr ComputePipelineIndirectBufferInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr ComputePipelineIndirectBufferInfoNV
p -> Ptr ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> IO b -> IO b
forall b.
Ptr ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ComputePipelineIndirectBufferInfoNV
p ComputePipelineIndirectBufferInfoNV
x (Ptr ComputePipelineIndirectBufferInfoNV -> IO b
f Ptr ComputePipelineIndirectBufferInfoNV
p)
pokeCStruct :: forall b.
Ptr ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> IO b -> IO b
pokeCStruct Ptr ComputePipelineIndirectBufferInfoNV
p ComputePipelineIndirectBufferInfoNV{DeviceAddress
$sel:deviceAddress:ComputePipelineIndirectBufferInfoNV :: ComputePipelineIndirectBufferInfoNV -> DeviceAddress
$sel:size:ComputePipelineIndirectBufferInfoNV :: ComputePipelineIndirectBufferInfoNV -> DeviceAddress
$sel:pipelineDeviceAddressCaptureReplay:ComputePipelineIndirectBufferInfoNV :: ComputePipelineIndirectBufferInfoNV -> DeviceAddress
deviceAddress :: DeviceAddress
size :: DeviceAddress
pipelineDeviceAddressCaptureReplay :: DeviceAddress
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMPUTE_PIPELINE_INDIRECT_BUFFER_INFO_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (DeviceAddress
deviceAddress)
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceAddress
size)
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceAddress)) (DeviceAddress
pipelineDeviceAddressCaptureReplay)
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ComputePipelineIndirectBufferInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr ComputePipelineIndirectBufferInfoNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMPUTE_PIPELINE_INDIRECT_BUFFER_INFO_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (DeviceAddress
forall a. Zero a => a
zero)
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceAddress
forall a. Zero a => a
zero)
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceAddress)) (DeviceAddress
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ComputePipelineIndirectBufferInfoNV where
peekCStruct :: Ptr ComputePipelineIndirectBufferInfoNV
-> IO ComputePipelineIndirectBufferInfoNV
peekCStruct Ptr ComputePipelineIndirectBufferInfoNV
p = do
DeviceAddress
deviceAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress))
DeviceAddress
size <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
DeviceAddress
pipelineDeviceAddressCaptureReplay <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr ComputePipelineIndirectBufferInfoNV
p Ptr ComputePipelineIndirectBufferInfoNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceAddress))
ComputePipelineIndirectBufferInfoNV
-> IO ComputePipelineIndirectBufferInfoNV
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ComputePipelineIndirectBufferInfoNV
-> IO ComputePipelineIndirectBufferInfoNV)
-> ComputePipelineIndirectBufferInfoNV
-> IO ComputePipelineIndirectBufferInfoNV
forall a b. (a -> b) -> a -> b
$ DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> ComputePipelineIndirectBufferInfoNV
ComputePipelineIndirectBufferInfoNV
DeviceAddress
deviceAddress DeviceAddress
size DeviceAddress
pipelineDeviceAddressCaptureReplay
instance Storable ComputePipelineIndirectBufferInfoNV where
sizeOf :: ComputePipelineIndirectBufferInfoNV -> Int
sizeOf ~ComputePipelineIndirectBufferInfoNV
_ = Int
40
alignment :: ComputePipelineIndirectBufferInfoNV -> Int
alignment ~ComputePipelineIndirectBufferInfoNV
_ = Int
8
peek :: Ptr ComputePipelineIndirectBufferInfoNV
-> IO ComputePipelineIndirectBufferInfoNV
peek = Ptr ComputePipelineIndirectBufferInfoNV
-> IO ComputePipelineIndirectBufferInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> IO ()
poke Ptr ComputePipelineIndirectBufferInfoNV
ptr ComputePipelineIndirectBufferInfoNV
poked = Ptr ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> IO () -> IO ()
forall b.
Ptr ComputePipelineIndirectBufferInfoNV
-> ComputePipelineIndirectBufferInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ComputePipelineIndirectBufferInfoNV
ptr ComputePipelineIndirectBufferInfoNV
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ComputePipelineIndirectBufferInfoNV where
zero :: ComputePipelineIndirectBufferInfoNV
zero = DeviceAddress
-> DeviceAddress
-> DeviceAddress
-> ComputePipelineIndirectBufferInfoNV
ComputePipelineIndirectBufferInfoNV
DeviceAddress
forall a. Zero a => a
zero
DeviceAddress
forall a. Zero a => a
zero
DeviceAddress
forall a. Zero a => a
zero
data PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV = PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
{
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
deviceGeneratedCompute :: Bool
,
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
deviceGeneratedComputePipelines :: Bool
,
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
deviceGeneratedComputeCaptureReplay :: Bool
}
deriving (Typeable, PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
(PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool)
-> (PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool)
-> Eq PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
== :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
$c/= :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
/= :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV)
#endif
deriving instance Show PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
instance ToCStruct PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> (Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b)
-> IO b
withCStruct PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
x Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> IO b
f = Int
-> (Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b)
-> IO b)
-> (Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p -> Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b
-> IO b
forall b.
Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
x (Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> IO b
f Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV{Bool
$sel:deviceGeneratedCompute:PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
$sel:deviceGeneratedComputePipelines:PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
$sel:deviceGeneratedComputeCaptureReplay:PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Bool
deviceGeneratedCompute :: Bool
deviceGeneratedComputePipelines :: Bool
deviceGeneratedComputeCaptureReplay :: Bool
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_COMPUTE_FEATURES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> 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 PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceGeneratedCompute))
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceGeneratedComputePipelines))
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceGeneratedComputeCaptureReplay))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_COMPUTE_FEATURES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> 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 PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> 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))
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
peekCStruct Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p = do
Bool32
deviceGeneratedCompute <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
deviceGeneratedComputePipelines <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
deviceGeneratedComputeCaptureReplay <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
p Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV)
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
deviceGeneratedCompute)
(Bool32 -> Bool
bool32ToBool Bool32
deviceGeneratedComputePipelines)
(Bool32 -> Bool
bool32ToBool Bool32
deviceGeneratedComputeCaptureReplay)
instance Storable PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV where
sizeOf :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Int
sizeOf ~PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
_ = Int
32
alignment :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> Int
alignment ~PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
peek = Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV -> IO ()
poke Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
poked = Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO ()
-> IO ()
forall b.
Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
ptr PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV where
zero :: PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
zero = Bool
-> Bool
-> Bool
-> PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
PhysicalDeviceDeviceGeneratedCommandsComputeFeaturesNV
Bool
forall a. Zero a => a
zero
Bool
forall a. Zero a => a
zero
Bool
forall a. Zero a => a
zero
data PipelineIndirectDeviceAddressInfoNV = PipelineIndirectDeviceAddressInfoNV
{
PipelineIndirectDeviceAddressInfoNV -> PipelineBindPoint
pipelineBindPoint :: PipelineBindPoint
,
PipelineIndirectDeviceAddressInfoNV -> Pipeline
pipeline :: Pipeline
}
deriving (Typeable, PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool
(PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool)
-> (PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool)
-> Eq PipelineIndirectDeviceAddressInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool
== :: PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool
$c/= :: PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool
/= :: PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineIndirectDeviceAddressInfoNV)
#endif
deriving instance Show PipelineIndirectDeviceAddressInfoNV
instance ToCStruct PipelineIndirectDeviceAddressInfoNV where
withCStruct :: forall b.
PipelineIndirectDeviceAddressInfoNV
-> (Ptr PipelineIndirectDeviceAddressInfoNV -> IO b) -> IO b
withCStruct PipelineIndirectDeviceAddressInfoNV
x Ptr PipelineIndirectDeviceAddressInfoNV -> IO b
f = Int -> (Ptr PipelineIndirectDeviceAddressInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PipelineIndirectDeviceAddressInfoNV -> IO b) -> IO b)
-> (Ptr PipelineIndirectDeviceAddressInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineIndirectDeviceAddressInfoNV
p -> Ptr PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> IO b -> IO b
forall b.
Ptr PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineIndirectDeviceAddressInfoNV
p PipelineIndirectDeviceAddressInfoNV
x (Ptr PipelineIndirectDeviceAddressInfoNV -> IO b
f Ptr PipelineIndirectDeviceAddressInfoNV
p)
pokeCStruct :: forall b.
Ptr PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> IO b -> IO b
pokeCStruct Ptr PipelineIndirectDeviceAddressInfoNV
p PipelineIndirectDeviceAddressInfoNV{PipelineBindPoint
Pipeline
$sel:pipelineBindPoint:PipelineIndirectDeviceAddressInfoNV :: PipelineIndirectDeviceAddressInfoNV -> PipelineBindPoint
$sel:pipeline:PipelineIndirectDeviceAddressInfoNV :: PipelineIndirectDeviceAddressInfoNV -> Pipeline
pipelineBindPoint :: PipelineBindPoint
pipeline :: Pipeline
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_INDIRECT_DEVICE_ADDRESS_INFO_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV
-> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineBindPoint)) (PipelineBindPoint
pipelineBindPoint)
Ptr Pipeline -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Pipeline)) (Pipeline
pipeline)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PipelineIndirectDeviceAddressInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr PipelineIndirectDeviceAddressInfoNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_INDIRECT_DEVICE_ADDRESS_INFO_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV
-> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineBindPoint)) (PipelineBindPoint
forall a. Zero a => a
zero)
Ptr Pipeline -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Pipeline)) (Pipeline
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PipelineIndirectDeviceAddressInfoNV where
peekCStruct :: Ptr PipelineIndirectDeviceAddressInfoNV
-> IO PipelineIndirectDeviceAddressInfoNV
peekCStruct Ptr PipelineIndirectDeviceAddressInfoNV
p = do
PipelineBindPoint
pipelineBindPoint <- forall a. Storable a => Ptr a -> IO a
peek @PipelineBindPoint ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV
-> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineBindPoint))
Pipeline
pipeline <- forall a. Storable a => Ptr a -> IO a
peek @Pipeline ((Ptr PipelineIndirectDeviceAddressInfoNV
p Ptr PipelineIndirectDeviceAddressInfoNV -> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Pipeline))
PipelineIndirectDeviceAddressInfoNV
-> IO PipelineIndirectDeviceAddressInfoNV
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineIndirectDeviceAddressInfoNV
-> IO PipelineIndirectDeviceAddressInfoNV)
-> PipelineIndirectDeviceAddressInfoNV
-> IO PipelineIndirectDeviceAddressInfoNV
forall a b. (a -> b) -> a -> b
$ PipelineBindPoint
-> Pipeline -> PipelineIndirectDeviceAddressInfoNV
PipelineIndirectDeviceAddressInfoNV
PipelineBindPoint
pipelineBindPoint Pipeline
pipeline
instance Storable PipelineIndirectDeviceAddressInfoNV where
sizeOf :: PipelineIndirectDeviceAddressInfoNV -> Int
sizeOf ~PipelineIndirectDeviceAddressInfoNV
_ = Int
32
alignment :: PipelineIndirectDeviceAddressInfoNV -> Int
alignment ~PipelineIndirectDeviceAddressInfoNV
_ = Int
8
peek :: Ptr PipelineIndirectDeviceAddressInfoNV
-> IO PipelineIndirectDeviceAddressInfoNV
peek = Ptr PipelineIndirectDeviceAddressInfoNV
-> IO PipelineIndirectDeviceAddressInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> IO ()
poke Ptr PipelineIndirectDeviceAddressInfoNV
ptr PipelineIndirectDeviceAddressInfoNV
poked = Ptr PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> IO () -> IO ()
forall b.
Ptr PipelineIndirectDeviceAddressInfoNV
-> PipelineIndirectDeviceAddressInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineIndirectDeviceAddressInfoNV
ptr PipelineIndirectDeviceAddressInfoNV
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineIndirectDeviceAddressInfoNV where
zero :: PipelineIndirectDeviceAddressInfoNV
zero = PipelineBindPoint
-> Pipeline -> PipelineIndirectDeviceAddressInfoNV
PipelineIndirectDeviceAddressInfoNV
PipelineBindPoint
forall a. Zero a => a
zero
Pipeline
forall a. Zero a => a
zero
data BindPipelineIndirectCommandNV = BindPipelineIndirectCommandNV
{
BindPipelineIndirectCommandNV -> DeviceAddress
pipelineAddress :: DeviceAddress }
deriving (Typeable, BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool
(BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool)
-> (BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool)
-> Eq BindPipelineIndirectCommandNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool
== :: BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool
$c/= :: BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool
/= :: BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BindPipelineIndirectCommandNV)
#endif
deriving instance Show BindPipelineIndirectCommandNV
instance ToCStruct BindPipelineIndirectCommandNV where
withCStruct :: forall b.
BindPipelineIndirectCommandNV
-> (Ptr BindPipelineIndirectCommandNV -> IO b) -> IO b
withCStruct BindPipelineIndirectCommandNV
x Ptr BindPipelineIndirectCommandNV -> IO b
f = Int -> (Ptr BindPipelineIndirectCommandNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 ((Ptr BindPipelineIndirectCommandNV -> IO b) -> IO b)
-> (Ptr BindPipelineIndirectCommandNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr BindPipelineIndirectCommandNV
p -> Ptr BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> IO b -> IO b
forall b.
Ptr BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BindPipelineIndirectCommandNV
p BindPipelineIndirectCommandNV
x (Ptr BindPipelineIndirectCommandNV -> IO b
f Ptr BindPipelineIndirectCommandNV
p)
pokeCStruct :: forall b.
Ptr BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> IO b -> IO b
pokeCStruct Ptr BindPipelineIndirectCommandNV
p BindPipelineIndirectCommandNV{DeviceAddress
$sel:pipelineAddress:BindPipelineIndirectCommandNV :: BindPipelineIndirectCommandNV -> DeviceAddress
pipelineAddress :: DeviceAddress
..} IO b
f = do
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindPipelineIndirectCommandNV
p Ptr BindPipelineIndirectCommandNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress)) (DeviceAddress
pipelineAddress)
IO b
f
cStructSize :: Int
cStructSize = Int
8
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr BindPipelineIndirectCommandNV -> IO b -> IO b
pokeZeroCStruct Ptr BindPipelineIndirectCommandNV
p IO b
f = do
Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindPipelineIndirectCommandNV
p Ptr BindPipelineIndirectCommandNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress)) (DeviceAddress
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct BindPipelineIndirectCommandNV where
peekCStruct :: Ptr BindPipelineIndirectCommandNV
-> IO BindPipelineIndirectCommandNV
peekCStruct Ptr BindPipelineIndirectCommandNV
p = do
DeviceAddress
pipelineAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr BindPipelineIndirectCommandNV
p Ptr BindPipelineIndirectCommandNV -> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress))
BindPipelineIndirectCommandNV -> IO BindPipelineIndirectCommandNV
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BindPipelineIndirectCommandNV -> IO BindPipelineIndirectCommandNV)
-> BindPipelineIndirectCommandNV
-> IO BindPipelineIndirectCommandNV
forall a b. (a -> b) -> a -> b
$ DeviceAddress -> BindPipelineIndirectCommandNV
BindPipelineIndirectCommandNV
DeviceAddress
pipelineAddress
instance Storable BindPipelineIndirectCommandNV where
sizeOf :: BindPipelineIndirectCommandNV -> Int
sizeOf ~BindPipelineIndirectCommandNV
_ = Int
8
alignment :: BindPipelineIndirectCommandNV -> Int
alignment ~BindPipelineIndirectCommandNV
_ = Int
8
peek :: Ptr BindPipelineIndirectCommandNV
-> IO BindPipelineIndirectCommandNV
peek = Ptr BindPipelineIndirectCommandNV
-> IO BindPipelineIndirectCommandNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> IO ()
poke Ptr BindPipelineIndirectCommandNV
ptr BindPipelineIndirectCommandNV
poked = Ptr BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> IO () -> IO ()
forall b.
Ptr BindPipelineIndirectCommandNV
-> BindPipelineIndirectCommandNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BindPipelineIndirectCommandNV
ptr BindPipelineIndirectCommandNV
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero BindPipelineIndirectCommandNV where
zero :: BindPipelineIndirectCommandNV
zero = DeviceAddress -> BindPipelineIndirectCommandNV
BindPipelineIndirectCommandNV
DeviceAddress
forall a. Zero a => a
zero
type NV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION = 2
pattern NV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION :: forall a. Integral a => a
$mNV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEVICE_GENERATED_COMMANDS_COMPUTE_SPEC_VERSION = 2
type NV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME = "VK_NV_device_generated_commands_compute"
pattern NV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEVICE_GENERATED_COMMANDS_COMPUTE_EXTENSION_NAME = "VK_NV_device_generated_commands_compute"