{-# language CPP #-}
module Vulkan.Extensions.VK_NV_copy_memory_indirect ( cmdCopyMemoryIndirectNV
, cmdCopyMemoryToImageIndirectNV
, CopyMemoryIndirectCommandNV(..)
, CopyMemoryToImageIndirectCommandNV(..)
, PhysicalDeviceCopyMemoryIndirectFeaturesNV(..)
, PhysicalDeviceCopyMemoryIndirectPropertiesNV(..)
, NV_COPY_MEMORY_INDIRECT_SPEC_VERSION
, pattern NV_COPY_MEMORY_INDIRECT_SPEC_VERSION
, NV_COPY_MEMORY_INDIRECT_EXTENSION_NAME
, pattern NV_COPY_MEMORY_INDIRECT_EXTENSION_NAME
) 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 qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
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.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
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.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyMemoryIndirectNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyMemoryToImageIndirectNV))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.FundamentalTypes (Extent3D)
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout(..))
import Vulkan.Core10.CommandBufferBuilding (ImageSubresourceLayers)
import Vulkan.Core10.FundamentalTypes (Offset3D)
import Vulkan.Core10.Enums.QueueFlagBits (QueueFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COPY_MEMORY_INDIRECT_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COPY_MEMORY_INDIRECT_PROPERTIES_NV))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdCopyMemoryIndirectNV
:: FunPtr (Ptr CommandBuffer_T -> DeviceAddress -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> DeviceAddress -> Word32 -> Word32 -> IO ()
cmdCopyMemoryIndirectNV :: forall io
. (MonadIO io)
=>
CommandBuffer
->
("copyBufferAddress" ::: DeviceAddress)
->
("copyCount" ::: Word32)
->
("stride" ::: Word32)
-> io ()
cmdCopyMemoryIndirectNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> io ()
cmdCopyMemoryIndirectNV CommandBuffer
commandBuffer
"copyBufferAddress" ::: DeviceAddress
copyBufferAddress
"copyCount" ::: Word32
copyCount
"copyCount" ::: Word32
stride = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let vkCmdCopyMemoryIndirectNVPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ())
vkCmdCopyMemoryIndirectNVPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ())
pVkCmdCopyMemoryIndirectNV (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ())
vkCmdCopyMemoryIndirectNVPtr 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 vkCmdCopyMemoryIndirectNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdCopyMemoryIndirectNV' :: Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ()
vkCmdCopyMemoryIndirectNV' = FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ())
-> Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ()
mkVkCmdCopyMemoryIndirectNV FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ())
vkCmdCopyMemoryIndirectNVPtr
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdCopyMemoryIndirectNV" (Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> IO ()
vkCmdCopyMemoryIndirectNV'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
("copyBufferAddress" ::: DeviceAddress
copyBufferAddress)
("copyCount" ::: Word32
copyCount)
("copyCount" ::: Word32
stride))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdCopyMemoryToImageIndirectNV
:: FunPtr (Ptr CommandBuffer_T -> DeviceAddress -> Word32 -> Word32 -> Image -> ImageLayout -> Ptr ImageSubresourceLayers -> IO ()) -> Ptr CommandBuffer_T -> DeviceAddress -> Word32 -> Word32 -> Image -> ImageLayout -> Ptr ImageSubresourceLayers -> IO ()
cmdCopyMemoryToImageIndirectNV :: forall io
. (MonadIO io)
=>
CommandBuffer
->
("copyBufferAddress" ::: DeviceAddress)
->
("stride" ::: Word32)
->
("dstImage" ::: Image)
->
("dstImageLayout" ::: ImageLayout)
->
("imageSubresources" ::: Vector ImageSubresourceLayers)
-> io ()
cmdCopyMemoryToImageIndirectNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("imageSubresources" ::: Vector ImageSubresourceLayers)
-> io ()
cmdCopyMemoryToImageIndirectNV CommandBuffer
commandBuffer
"copyBufferAddress" ::: DeviceAddress
copyBufferAddress
"copyCount" ::: Word32
stride
"dstImage" ::: Image
dstImage
"dstImageLayout" ::: ImageLayout
dstImageLayout
"imageSubresources" ::: Vector ImageSubresourceLayers
imageSubresources = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkCmdCopyMemoryToImageIndirectNVPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ())
vkCmdCopyMemoryToImageIndirectNVPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ())
pVkCmdCopyMemoryToImageIndirectNV (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ())
vkCmdCopyMemoryToImageIndirectNVPtr 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 vkCmdCopyMemoryToImageIndirectNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdCopyMemoryToImageIndirectNV' :: Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ()
vkCmdCopyMemoryToImageIndirectNV' = FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ())
-> Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ()
mkVkCmdCopyMemoryToImageIndirectNV FunPtr
(Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ())
vkCmdCopyMemoryToImageIndirectNVPtr
"pImageSubresources" ::: Ptr ImageSubresourceLayers
pPImageSubresources <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @ImageSubresourceLayers ((forall a. Vector a -> Int
Data.Vector.length ("imageSubresources" ::: Vector ImageSubresourceLayers
imageSubresources)) forall a. Num a => a -> a -> a
* Int
16)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ImageSubresourceLayers
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pImageSubresources" ::: Ptr ImageSubresourceLayers
pPImageSubresources forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
16 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageSubresourceLayers) (ImageSubresourceLayers
e)) ("imageSubresources" ::: Vector ImageSubresourceLayers
imageSubresources)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdCopyMemoryToImageIndirectNV" (Ptr CommandBuffer_T
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ("dstImage" ::: Image)
-> ("dstImageLayout" ::: ImageLayout)
-> ("pImageSubresources" ::: Ptr ImageSubresourceLayers)
-> IO ()
vkCmdCopyMemoryToImageIndirectNV'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
("copyBufferAddress" ::: DeviceAddress
copyBufferAddress)
((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("imageSubresources" ::: Vector ImageSubresourceLayers
imageSubresources)) :: Word32))
("copyCount" ::: Word32
stride)
("dstImage" ::: Image
dstImage)
("dstImageLayout" ::: ImageLayout
dstImageLayout)
("pImageSubresources" ::: Ptr ImageSubresourceLayers
pPImageSubresources))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
data CopyMemoryIndirectCommandNV = CopyMemoryIndirectCommandNV
{
CopyMemoryIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
srcAddress :: DeviceAddress
,
CopyMemoryIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
dstAddress :: DeviceAddress
,
CopyMemoryIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
size :: DeviceSize
}
deriving (Typeable, CopyMemoryIndirectCommandNV -> CopyMemoryIndirectCommandNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyMemoryIndirectCommandNV -> CopyMemoryIndirectCommandNV -> Bool
$c/= :: CopyMemoryIndirectCommandNV -> CopyMemoryIndirectCommandNV -> Bool
== :: CopyMemoryIndirectCommandNV -> CopyMemoryIndirectCommandNV -> Bool
$c== :: CopyMemoryIndirectCommandNV -> CopyMemoryIndirectCommandNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyMemoryIndirectCommandNV)
#endif
deriving instance Show CopyMemoryIndirectCommandNV
instance ToCStruct CopyMemoryIndirectCommandNV where
withCStruct :: forall b.
CopyMemoryIndirectCommandNV
-> (Ptr CopyMemoryIndirectCommandNV -> IO b) -> IO b
withCStruct CopyMemoryIndirectCommandNV
x Ptr CopyMemoryIndirectCommandNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr CopyMemoryIndirectCommandNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CopyMemoryIndirectCommandNV
p CopyMemoryIndirectCommandNV
x (Ptr CopyMemoryIndirectCommandNV -> IO b
f Ptr CopyMemoryIndirectCommandNV
p)
pokeCStruct :: forall b.
Ptr CopyMemoryIndirectCommandNV
-> CopyMemoryIndirectCommandNV -> IO b -> IO b
pokeCStruct Ptr CopyMemoryIndirectCommandNV
p CopyMemoryIndirectCommandNV{"copyBufferAddress" ::: DeviceAddress
size :: "copyBufferAddress" ::: DeviceAddress
dstAddress :: "copyBufferAddress" ::: DeviceAddress
srcAddress :: "copyBufferAddress" ::: DeviceAddress
$sel:size:CopyMemoryIndirectCommandNV :: CopyMemoryIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
$sel:dstAddress:CopyMemoryIndirectCommandNV :: CopyMemoryIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
$sel:srcAddress:CopyMemoryIndirectCommandNV :: CopyMemoryIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress)) ("copyBufferAddress" ::: DeviceAddress
srcAddress)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr DeviceAddress)) ("copyBufferAddress" ::: DeviceAddress
dstAddress)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) ("copyBufferAddress" ::: DeviceAddress
size)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr CopyMemoryIndirectCommandNV -> IO b -> IO b
pokeZeroCStruct Ptr CopyMemoryIndirectCommandNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr DeviceAddress)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct CopyMemoryIndirectCommandNV where
peekCStruct :: Ptr CopyMemoryIndirectCommandNV -> IO CopyMemoryIndirectCommandNV
peekCStruct Ptr CopyMemoryIndirectCommandNV
p = do
"copyBufferAddress" ::: DeviceAddress
srcAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress))
"copyBufferAddress" ::: DeviceAddress
dstAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr DeviceAddress))
"copyBufferAddress" ::: DeviceAddress
size <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr CopyMemoryIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("copyBufferAddress" ::: DeviceAddress)
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyBufferAddress" ::: DeviceAddress)
-> CopyMemoryIndirectCommandNV
CopyMemoryIndirectCommandNV
"copyBufferAddress" ::: DeviceAddress
srcAddress "copyBufferAddress" ::: DeviceAddress
dstAddress "copyBufferAddress" ::: DeviceAddress
size
instance Storable CopyMemoryIndirectCommandNV where
sizeOf :: CopyMemoryIndirectCommandNV -> Int
sizeOf ~CopyMemoryIndirectCommandNV
_ = Int
24
alignment :: CopyMemoryIndirectCommandNV -> Int
alignment ~CopyMemoryIndirectCommandNV
_ = Int
8
peek :: Ptr CopyMemoryIndirectCommandNV -> IO CopyMemoryIndirectCommandNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr CopyMemoryIndirectCommandNV
-> CopyMemoryIndirectCommandNV -> IO ()
poke Ptr CopyMemoryIndirectCommandNV
ptr CopyMemoryIndirectCommandNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CopyMemoryIndirectCommandNV
ptr CopyMemoryIndirectCommandNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero CopyMemoryIndirectCommandNV where
zero :: CopyMemoryIndirectCommandNV
zero = ("copyBufferAddress" ::: DeviceAddress)
-> ("copyBufferAddress" ::: DeviceAddress)
-> ("copyBufferAddress" ::: DeviceAddress)
-> CopyMemoryIndirectCommandNV
CopyMemoryIndirectCommandNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data CopyMemoryToImageIndirectCommandNV = CopyMemoryToImageIndirectCommandNV
{
CopyMemoryToImageIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
srcAddress :: DeviceAddress
,
CopyMemoryToImageIndirectCommandNV -> "copyCount" ::: Word32
bufferRowLength :: Word32
,
CopyMemoryToImageIndirectCommandNV -> "copyCount" ::: Word32
bufferImageHeight :: Word32
,
CopyMemoryToImageIndirectCommandNV -> ImageSubresourceLayers
imageSubresource :: ImageSubresourceLayers
,
CopyMemoryToImageIndirectCommandNV -> Offset3D
imageOffset :: Offset3D
,
CopyMemoryToImageIndirectCommandNV -> Extent3D
imageExtent :: Extent3D
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyMemoryToImageIndirectCommandNV)
#endif
deriving instance Show CopyMemoryToImageIndirectCommandNV
instance ToCStruct CopyMemoryToImageIndirectCommandNV where
withCStruct :: forall b.
CopyMemoryToImageIndirectCommandNV
-> (Ptr CopyMemoryToImageIndirectCommandNV -> IO b) -> IO b
withCStruct CopyMemoryToImageIndirectCommandNV
x Ptr CopyMemoryToImageIndirectCommandNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
56 forall a b. (a -> b) -> a -> b
$ \Ptr CopyMemoryToImageIndirectCommandNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CopyMemoryToImageIndirectCommandNV
p CopyMemoryToImageIndirectCommandNV
x (Ptr CopyMemoryToImageIndirectCommandNV -> IO b
f Ptr CopyMemoryToImageIndirectCommandNV
p)
pokeCStruct :: forall b.
Ptr CopyMemoryToImageIndirectCommandNV
-> CopyMemoryToImageIndirectCommandNV -> IO b -> IO b
pokeCStruct Ptr CopyMemoryToImageIndirectCommandNV
p CopyMemoryToImageIndirectCommandNV{"copyCount" ::: Word32
"copyBufferAddress" ::: DeviceAddress
ImageSubresourceLayers
Offset3D
Extent3D
imageExtent :: Extent3D
imageOffset :: Offset3D
imageSubresource :: ImageSubresourceLayers
bufferImageHeight :: "copyCount" ::: Word32
bufferRowLength :: "copyCount" ::: Word32
srcAddress :: "copyBufferAddress" ::: DeviceAddress
$sel:imageExtent:CopyMemoryToImageIndirectCommandNV :: CopyMemoryToImageIndirectCommandNV -> Extent3D
$sel:imageOffset:CopyMemoryToImageIndirectCommandNV :: CopyMemoryToImageIndirectCommandNV -> Offset3D
$sel:imageSubresource:CopyMemoryToImageIndirectCommandNV :: CopyMemoryToImageIndirectCommandNV -> ImageSubresourceLayers
$sel:bufferImageHeight:CopyMemoryToImageIndirectCommandNV :: CopyMemoryToImageIndirectCommandNV -> "copyCount" ::: Word32
$sel:bufferRowLength:CopyMemoryToImageIndirectCommandNV :: CopyMemoryToImageIndirectCommandNV -> "copyCount" ::: Word32
$sel:srcAddress:CopyMemoryToImageIndirectCommandNV :: CopyMemoryToImageIndirectCommandNV
-> "copyBufferAddress" ::: DeviceAddress
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress)) ("copyBufferAddress" ::: DeviceAddress
srcAddress)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) ("copyCount" ::: Word32
bufferRowLength)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32)) ("copyCount" ::: Word32
bufferImageHeight)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
imageSubresource)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Offset3D)) (Offset3D
imageOffset)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Extent3D)) (Extent3D
imageExtent)
IO b
f
cStructSize :: Int
cStructSize = Int
56
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr CopyMemoryToImageIndirectCommandNV -> IO b -> IO b
pokeZeroCStruct Ptr CopyMemoryToImageIndirectCommandNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Offset3D)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Extent3D)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct CopyMemoryToImageIndirectCommandNV where
peekCStruct :: Ptr CopyMemoryToImageIndirectCommandNV
-> IO CopyMemoryToImageIndirectCommandNV
peekCStruct Ptr CopyMemoryToImageIndirectCommandNV
p = do
"copyBufferAddress" ::: DeviceAddress
srcAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr DeviceAddress))
"copyCount" ::: Word32
bufferRowLength <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
"copyCount" ::: Word32
bufferImageHeight <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32))
ImageSubresourceLayers
imageSubresource <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageSubresourceLayers))
Offset3D
imageOffset <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Offset3D))
Extent3D
imageExtent <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D ((Ptr CopyMemoryToImageIndirectCommandNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Extent3D))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> CopyMemoryToImageIndirectCommandNV
CopyMemoryToImageIndirectCommandNV
"copyBufferAddress" ::: DeviceAddress
srcAddress
"copyCount" ::: Word32
bufferRowLength
"copyCount" ::: Word32
bufferImageHeight
ImageSubresourceLayers
imageSubresource
Offset3D
imageOffset
Extent3D
imageExtent
instance Storable CopyMemoryToImageIndirectCommandNV where
sizeOf :: CopyMemoryToImageIndirectCommandNV -> Int
sizeOf ~CopyMemoryToImageIndirectCommandNV
_ = Int
56
alignment :: CopyMemoryToImageIndirectCommandNV -> Int
alignment ~CopyMemoryToImageIndirectCommandNV
_ = Int
8
peek :: Ptr CopyMemoryToImageIndirectCommandNV
-> IO CopyMemoryToImageIndirectCommandNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr CopyMemoryToImageIndirectCommandNV
-> CopyMemoryToImageIndirectCommandNV -> IO ()
poke Ptr CopyMemoryToImageIndirectCommandNV
ptr CopyMemoryToImageIndirectCommandNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CopyMemoryToImageIndirectCommandNV
ptr CopyMemoryToImageIndirectCommandNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero CopyMemoryToImageIndirectCommandNV where
zero :: CopyMemoryToImageIndirectCommandNV
zero = ("copyBufferAddress" ::: DeviceAddress)
-> ("copyCount" ::: Word32)
-> ("copyCount" ::: Word32)
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> CopyMemoryToImageIndirectCommandNV
CopyMemoryToImageIndirectCommandNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceCopyMemoryIndirectFeaturesNV = PhysicalDeviceCopyMemoryIndirectFeaturesNV
{
PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
indirectCopy :: Bool }
deriving (Typeable, PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
$c/= :: PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
== :: PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
$c== :: PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCopyMemoryIndirectFeaturesNV)
#endif
deriving instance Show PhysicalDeviceCopyMemoryIndirectFeaturesNV
instance ToCStruct PhysicalDeviceCopyMemoryIndirectFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> (Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceCopyMemoryIndirectFeaturesNV
x Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p PhysicalDeviceCopyMemoryIndirectFeaturesNV
x (Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV -> IO b
f Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p PhysicalDeviceCopyMemoryIndirectFeaturesNV{Bool
indirectCopy :: Bool
$sel:indirectCopy:PhysicalDeviceCopyMemoryIndirectFeaturesNV :: PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COPY_MEMORY_INDIRECT_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
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 PhysicalDeviceCopyMemoryIndirectFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
indirectCopy))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COPY_MEMORY_INDIRECT_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
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 PhysicalDeviceCopyMemoryIndirectFeaturesNV
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 PhysicalDeviceCopyMemoryIndirectFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> IO PhysicalDeviceCopyMemoryIndirectFeaturesNV
peekCStruct Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
p = do
Bool32
indirectCopy <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
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 -> PhysicalDeviceCopyMemoryIndirectFeaturesNV
PhysicalDeviceCopyMemoryIndirectFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
indirectCopy)
instance Storable PhysicalDeviceCopyMemoryIndirectFeaturesNV where
sizeOf :: PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Int
sizeOf ~PhysicalDeviceCopyMemoryIndirectFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceCopyMemoryIndirectFeaturesNV -> Int
alignment ~PhysicalDeviceCopyMemoryIndirectFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> IO PhysicalDeviceCopyMemoryIndirectFeaturesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
-> PhysicalDeviceCopyMemoryIndirectFeaturesNV -> IO ()
poke Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
ptr PhysicalDeviceCopyMemoryIndirectFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCopyMemoryIndirectFeaturesNV where
zero :: PhysicalDeviceCopyMemoryIndirectFeaturesNV
zero = Bool -> PhysicalDeviceCopyMemoryIndirectFeaturesNV
PhysicalDeviceCopyMemoryIndirectFeaturesNV
forall a. Zero a => a
zero
data PhysicalDeviceCopyMemoryIndirectPropertiesNV = PhysicalDeviceCopyMemoryIndirectPropertiesNV
{
PhysicalDeviceCopyMemoryIndirectPropertiesNV -> QueueFlags
supportedQueues :: QueueFlags }
deriving (Typeable, PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Bool
$c/= :: PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Bool
== :: PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Bool
$c== :: PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCopyMemoryIndirectPropertiesNV)
#endif
deriving instance Show PhysicalDeviceCopyMemoryIndirectPropertiesNV
instance ToCStruct PhysicalDeviceCopyMemoryIndirectPropertiesNV where
withCStruct :: forall b.
PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> (Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV -> IO b)
-> IO b
withCStruct PhysicalDeviceCopyMemoryIndirectPropertiesNV
x Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p PhysicalDeviceCopyMemoryIndirectPropertiesNV
x (Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV -> IO b
f Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p PhysicalDeviceCopyMemoryIndirectPropertiesNV{QueueFlags
supportedQueues :: QueueFlags
$sel:supportedQueues:PhysicalDeviceCopyMemoryIndirectPropertiesNV :: PhysicalDeviceCopyMemoryIndirectPropertiesNV -> QueueFlags
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COPY_MEMORY_INDIRECT_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
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 PhysicalDeviceCopyMemoryIndirectPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueueFlags)) (QueueFlags
supportedQueues)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COPY_MEMORY_INDIRECT_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
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 PhysicalDeviceCopyMemoryIndirectPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueueFlags)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceCopyMemoryIndirectPropertiesNV where
peekCStruct :: Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> IO PhysicalDeviceCopyMemoryIndirectPropertiesNV
peekCStruct Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p = do
QueueFlags
supportedQueues <- forall a. Storable a => Ptr a -> IO a
peek @QueueFlags ((Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueueFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ QueueFlags -> PhysicalDeviceCopyMemoryIndirectPropertiesNV
PhysicalDeviceCopyMemoryIndirectPropertiesNV
QueueFlags
supportedQueues
instance Storable PhysicalDeviceCopyMemoryIndirectPropertiesNV where
sizeOf :: PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Int
sizeOf ~PhysicalDeviceCopyMemoryIndirectPropertiesNV
_ = Int
24
alignment :: PhysicalDeviceCopyMemoryIndirectPropertiesNV -> Int
alignment ~PhysicalDeviceCopyMemoryIndirectPropertiesNV
_ = Int
8
peek :: Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> IO PhysicalDeviceCopyMemoryIndirectPropertiesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
-> PhysicalDeviceCopyMemoryIndirectPropertiesNV -> IO ()
poke Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
ptr PhysicalDeviceCopyMemoryIndirectPropertiesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCopyMemoryIndirectPropertiesNV where
zero :: PhysicalDeviceCopyMemoryIndirectPropertiesNV
zero = QueueFlags -> PhysicalDeviceCopyMemoryIndirectPropertiesNV
PhysicalDeviceCopyMemoryIndirectPropertiesNV
forall a. Zero a => a
zero
type NV_COPY_MEMORY_INDIRECT_SPEC_VERSION = 1
pattern NV_COPY_MEMORY_INDIRECT_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_COPY_MEMORY_INDIRECT_SPEC_VERSION :: forall a. Integral a => a
$mNV_COPY_MEMORY_INDIRECT_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_COPY_MEMORY_INDIRECT_SPEC_VERSION = 1
type NV_COPY_MEMORY_INDIRECT_EXTENSION_NAME = "VK_NV_copy_memory_indirect"
pattern NV_COPY_MEMORY_INDIRECT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_COPY_MEMORY_INDIRECT_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_COPY_MEMORY_INDIRECT_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_COPY_MEMORY_INDIRECT_EXTENSION_NAME = "VK_NV_copy_memory_indirect"