{-# language CPP #-}
module Vulkan.Core10.OtherTypes  ( MemoryBarrier(..)
                                 , BufferMemoryBarrier(..)
                                 , ImageMemoryBarrier(..)
                                 , DrawIndirectCommand(..)
                                 , DrawIndexedIndirectCommand(..)
                                 , DispatchIndirectCommand(..)
                                 , BaseOutStructure(..)
                                 , BaseInStructure(..)
                                 , ObjectType(..)
                                 , VendorId(..)
                                 ) where

import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.Ptr (castPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Type.Equality ((:~:)(Refl))
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 Data.Int (Int32)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.Core10.ImageView (ImageSubresourceRange)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_sample_locations (SampleLocationsInfoEXT)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_BARRIER))
import Vulkan.CStruct.Extends (BaseInStructure(..))
import Vulkan.CStruct.Extends (BaseOutStructure(..))
import Vulkan.Core10.Enums.ObjectType (ObjectType(..))
import Vulkan.Core10.Enums.VendorId (VendorId(..))
-- | VkMemoryBarrier - Structure specifying a global memory barrier
--
-- = Description
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access types in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>
-- specified by @srcAccessMask@.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access types in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>
-- specified by @dstAccessMask@.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdPipelineBarrier',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWaitEvents'
data MemoryBarrier = MemoryBarrier
  { -- | @srcAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>.
    --
    -- @srcAccessMask@ /must/ be a valid combination of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' values
    MemoryBarrier -> AccessFlags
srcAccessMask :: AccessFlags
  , -- | @dstAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>.
    --
    -- @dstAccessMask@ /must/ be a valid combination of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' values
    MemoryBarrier -> AccessFlags
dstAccessMask :: AccessFlags
  }
  deriving (Typeable, MemoryBarrier -> MemoryBarrier -> Bool
(MemoryBarrier -> MemoryBarrier -> Bool)
-> (MemoryBarrier -> MemoryBarrier -> Bool) -> Eq MemoryBarrier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryBarrier -> MemoryBarrier -> Bool
$c/= :: MemoryBarrier -> MemoryBarrier -> Bool
== :: MemoryBarrier -> MemoryBarrier -> Bool
$c== :: MemoryBarrier -> MemoryBarrier -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryBarrier)
#endif
deriving instance Show MemoryBarrier

instance ToCStruct MemoryBarrier where
  withCStruct :: MemoryBarrier -> (Ptr MemoryBarrier -> IO b) -> IO b
withCStruct x :: MemoryBarrier
x f :: Ptr MemoryBarrier -> IO b
f = Int -> Int -> (Ptr MemoryBarrier -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr MemoryBarrier -> IO b) -> IO b)
-> (Ptr MemoryBarrier -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryBarrier
p -> Ptr MemoryBarrier -> MemoryBarrier -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryBarrier
p MemoryBarrier
x (Ptr MemoryBarrier -> IO b
f Ptr MemoryBarrier
p)
  pokeCStruct :: Ptr MemoryBarrier -> MemoryBarrier -> IO b -> IO b
pokeCStruct p :: Ptr MemoryBarrier
p MemoryBarrier{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_BARRIER)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr MemoryBarrier -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryBarrier
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_BARRIER)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct MemoryBarrier where
  peekCStruct :: Ptr MemoryBarrier -> IO MemoryBarrier
peekCStruct p :: Ptr MemoryBarrier
p = do
    AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags))
    AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags))
    MemoryBarrier -> IO MemoryBarrier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryBarrier -> IO MemoryBarrier)
-> MemoryBarrier -> IO MemoryBarrier
forall a b. (a -> b) -> a -> b
$ AccessFlags -> AccessFlags -> MemoryBarrier
MemoryBarrier
             AccessFlags
srcAccessMask AccessFlags
dstAccessMask

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

instance Zero MemoryBarrier where
  zero :: MemoryBarrier
zero = AccessFlags -> AccessFlags -> MemoryBarrier
MemoryBarrier
           AccessFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero


-- | VkBufferMemoryBarrier - Structure specifying a buffer memory barrier
--
-- = Description
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access to memory through the specified buffer range, via
-- access types in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>
-- specified by @srcAccessMask@. If @srcAccessMask@ includes
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_WRITE_BIT', memory
-- writes performed by that access type are also made visible, as that
-- access type is not performed through a resource.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access to memory through the specified buffer range, via
-- access types in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>
-- specified by @dstAccessMask@. If @dstAccessMask@ includes
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_WRITE_BIT' or
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_READ_BIT', available
-- memory writes are also made visible to accesses of those types, as those
-- access types are not performed through a resource.
--
-- If @srcQueueFamilyIndex@ is not equal to @dstQueueFamilyIndex@, and
-- @srcQueueFamilyIndex@ is equal to the current queue family, then the
-- memory barrier defines a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-release queue family release operation>
-- for the specified buffer range, and the second access scope includes no
-- access, as if @dstAccessMask@ was @0@.
--
-- If @dstQueueFamilyIndex@ is not equal to @srcQueueFamilyIndex@, and
-- @dstQueueFamilyIndex@ is equal to the current queue family, then the
-- memory barrier defines a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-acquire queue family acquire operation>
-- for the specified buffer range, and the first access scope includes no
-- access, as if @srcAccessMask@ was @0@.
--
-- == Valid Usage
--
-- -   @offset@ /must/ be less than the size of @buffer@
--
-- -   If @size@ is not equal to 'Vulkan.Core10.APIConstants.WHOLE_SIZE',
--     @size@ /must/ be greater than @0@
--
-- -   If @size@ is not equal to 'Vulkan.Core10.APIConstants.WHOLE_SIZE',
--     @size@ /must/ be less than or equal to than the size of @buffer@
--     minus @offset@
--
-- -   If @buffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   If @srcQueueFamilyIndex@ is not equal to @dstQueueFamilyIndex@, at
--     least one /must/ not be a special queue family reserved for external
--     memory ownership transfers, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers ???>
--
-- -   If @buffer@ was created with a sharing mode of
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT',
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ are not equal, and
--     one of @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ is a special
--     queue family values reserved for external memory transfers, the
--     other /must/ be 'Vulkan.Core10.APIConstants.QUEUE_FAMILY_IGNORED'
--
-- -   If @buffer@ was created with a sharing mode of
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_EXCLUSIVE', and
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ are not equal,
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ /must/ both be valid
--     queue families, or one of the special queue family values reserved
--     for external memory transfers, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers ???>
--
-- -   If @buffer@ was created with a sharing mode of
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT', at least
--     one of @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ /must/ be
--     'Vulkan.Core10.APIConstants.QUEUE_FAMILY_IGNORED'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlags',
-- 'Vulkan.Core10.Handles.Buffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdPipelineBarrier',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWaitEvents'
data BufferMemoryBarrier = BufferMemoryBarrier
  { -- | @srcAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>.
    BufferMemoryBarrier -> AccessFlags
srcAccessMask :: AccessFlags
  , -- | @dstAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>.
    BufferMemoryBarrier -> AccessFlags
dstAccessMask :: AccessFlags
  , -- | @srcQueueFamilyIndex@ is the source queue family for a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>.
    BufferMemoryBarrier -> Word32
srcQueueFamilyIndex :: Word32
  , -- | @dstQueueFamilyIndex@ is the destination queue family for a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>.
    BufferMemoryBarrier -> Word32
dstQueueFamilyIndex :: Word32
  , -- | @buffer@ is a handle to the buffer whose backing memory is affected by
    -- the barrier.
    BufferMemoryBarrier -> Buffer
buffer :: Buffer
  , -- | @offset@ is an offset in bytes into the backing memory for @buffer@;
    -- this is relative to the base offset as bound to the buffer (see
    -- 'Vulkan.Core10.MemoryManagement.bindBufferMemory').
    BufferMemoryBarrier -> DeviceSize
offset :: DeviceSize
  , -- | @size@ is a size in bytes of the affected area of backing memory for
    -- @buffer@, or 'Vulkan.Core10.APIConstants.WHOLE_SIZE' to use the range
    -- from @offset@ to the end of the buffer.
    BufferMemoryBarrier -> DeviceSize
size :: DeviceSize
  }
  deriving (Typeable, BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
(BufferMemoryBarrier -> BufferMemoryBarrier -> Bool)
-> (BufferMemoryBarrier -> BufferMemoryBarrier -> Bool)
-> Eq BufferMemoryBarrier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
$c/= :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
== :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
$c== :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferMemoryBarrier)
#endif
deriving instance Show BufferMemoryBarrier

instance ToCStruct BufferMemoryBarrier where
  withCStruct :: BufferMemoryBarrier -> (Ptr BufferMemoryBarrier -> IO b) -> IO b
withCStruct x :: BufferMemoryBarrier
x f :: Ptr BufferMemoryBarrier -> IO b
f = Int -> Int -> (Ptr BufferMemoryBarrier -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((Ptr BufferMemoryBarrier -> IO b) -> IO b)
-> (Ptr BufferMemoryBarrier -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr BufferMemoryBarrier
p -> Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BufferMemoryBarrier
p BufferMemoryBarrier
x (Ptr BufferMemoryBarrier -> IO b
f Ptr BufferMemoryBarrier
p)
  pokeCStruct :: Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO b -> IO b
pokeCStruct p :: Ptr BufferMemoryBarrier
p BufferMemoryBarrier{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
srcQueueFamilyIndex)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
dstQueueFamilyIndex)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Buffer)) (Buffer
buffer)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) (DeviceSize
offset)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) (DeviceSize
size)
    IO b
f
  cStructSize :: Int
cStructSize = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr BufferMemoryBarrier -> IO b -> IO b
pokeZeroCStruct p :: Ptr BufferMemoryBarrier
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct BufferMemoryBarrier where
  peekCStruct :: Ptr BufferMemoryBarrier -> IO BufferMemoryBarrier
peekCStruct p :: Ptr BufferMemoryBarrier
p = do
    AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags))
    AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags))
    Word32
srcQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Word32
dstQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Buffer))
    DeviceSize
offset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize))
    DeviceSize
size <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize))
    BufferMemoryBarrier -> IO BufferMemoryBarrier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferMemoryBarrier -> IO BufferMemoryBarrier)
-> BufferMemoryBarrier -> IO BufferMemoryBarrier
forall a b. (a -> b) -> a -> b
$ AccessFlags
-> AccessFlags
-> Word32
-> Word32
-> Buffer
-> DeviceSize
-> DeviceSize
-> BufferMemoryBarrier
BufferMemoryBarrier
             AccessFlags
srcAccessMask AccessFlags
dstAccessMask Word32
srcQueueFamilyIndex Word32
dstQueueFamilyIndex Buffer
buffer DeviceSize
offset DeviceSize
size

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

instance Zero BufferMemoryBarrier where
  zero :: BufferMemoryBarrier
zero = AccessFlags
-> AccessFlags
-> Word32
-> Word32
-> Buffer
-> DeviceSize
-> DeviceSize
-> BufferMemoryBarrier
BufferMemoryBarrier
           AccessFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Buffer
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero


-- | VkImageMemoryBarrier - Structure specifying the parameters of an image
-- memory barrier
--
-- = Description
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access to memory through the specified image subresource
-- range, via access types in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>
-- specified by @srcAccessMask@. If @srcAccessMask@ includes
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_WRITE_BIT', memory
-- writes performed by that access type are also made visible, as that
-- access type is not performed through a resource.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access to memory through the specified image subresource
-- range, via access types in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>
-- specified by @dstAccessMask@. If @dstAccessMask@ includes
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_WRITE_BIT' or
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_READ_BIT', available
-- memory writes are also made visible to accesses of those types, as those
-- access types are not performed through a resource.
--
-- If @srcQueueFamilyIndex@ is not equal to @dstQueueFamilyIndex@, and
-- @srcQueueFamilyIndex@ is equal to the current queue family, then the
-- memory barrier defines a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-release queue family release operation>
-- for the specified image subresource range, and the second access scope
-- includes no access, as if @dstAccessMask@ was @0@.
--
-- If @dstQueueFamilyIndex@ is not equal to @srcQueueFamilyIndex@, and
-- @dstQueueFamilyIndex@ is equal to the current queue family, then the
-- memory barrier defines a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-acquire queue family acquire operation>
-- for the specified image subresource range, and the first access scope
-- includes no access, as if @srcAccessMask@ was @0@.
--
-- @oldLayout@ and @newLayout@ define an
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>
-- for the specified image subresource range.
--
-- If @image@ has a multi-planar format and the image is /disjoint/, then
-- including
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' in the
-- @aspectMask@ member of @subresourceRange@ is equivalent to including
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', and
-- (for three-plane formats only)
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'.
--
-- == Valid Usage
--
-- -   @subresourceRange.baseMipLevel@ /must/ be less than the @mipLevels@
--     specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was
--     created
--
-- -   If @subresourceRange.levelCount@ is not
--     'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS',
--     @subresourceRange.baseMipLevel@ + @subresourceRange.levelCount@
--     /must/ be less than or equal to the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created
--
-- -   @subresourceRange.baseArrayLayer@ /must/ be less than the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @image@ was created
--
-- -   If @subresourceRange.layerCount@ is not
--     'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS',
--     @subresourceRange.baseArrayLayer@ + @subresourceRange.layerCount@
--     /must/ be less than or equal to the @arrayLayers@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created
--
-- -   If @image@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT' or
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     @oldLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' or the
--     current layout of the image subresources affected by the barrier
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     @newLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED'
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Extensions.VK_KHR_separate_depth_stencil_layouts.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL_KHR'
--     then @image@ /must/ have been created with at least one of
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT',
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', or
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Extensions.VK_KHR_separate_depth_stencil_layouts.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL_KHR'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Extensions.VK_KHR_separate_depth_stencil_layouts.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL_KHR'
--     then @image@ /must/ have been created with at least one of
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT',
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', or
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Extensions.VK_KHR_separate_depth_stencil_layouts.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL_KHR'
--     then @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     set
--
-- -   If @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
--     or @oldLayout@ and @newLayout@ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>,
--     and @oldLayout@ or @newLayout@ is
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.IMAGE_LAYOUT_FRAGMENT_SHADING_RATE_ATTACHMENT_OPTIMAL_KHR'
--     then @image@ /must/ have been created with
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR'
--     set
--
-- -   If @image@ has a single-plane color format or is not /disjoint/,
--     then the @aspectMask@ member of @subresourceRange@ /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'
--
-- -   If @image@ has a multi-planar format and the image is /disjoint/,
--     then the @aspectMask@ member of @subresourceRange@ /must/ include
--     either at least one of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT',
--     and
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT';
--     or /must/ include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'
--
-- -   If @image@ has a multi-planar format with only two planes, then the
--     @aspectMask@ member of @subresourceRange@ /must/ not include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--
-- -   If @image@ has a depth\/stencil format with both depth and stencil
--     and the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
--     feature is enabled, then the @aspectMask@ member of
--     @subresourceRange@ /must/ include either or both
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' and
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--
-- -   If @image@ has a depth\/stencil format with both depth and stencil
--     and the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
--     feature is not enabled, then the @aspectMask@ member of
--     @subresourceRange@ /must/ include both
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' and
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--
-- -   If @srcQueueFamilyIndex@ is not equal to @dstQueueFamilyIndex@, at
--     least one /must/ not be a special queue family reserved for external
--     memory ownership transfers, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers ???>
--
-- -   If @image@ was created with a sharing mode of
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT',
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ are not equal, and
--     one of @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ is a special
--     queue family values reserved for external memory transfers, the
--     other /must/ be 'Vulkan.Core10.APIConstants.QUEUE_FAMILY_IGNORED'
--
-- -   If @image@ was created with a sharing mode of
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_EXCLUSIVE', and
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ are not equal,
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ /must/ both be valid
--     queue families, or one of the special queue family values reserved
--     for external memory transfers, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers ???>
--
-- -   If @image@ was created with a sharing mode of
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT', at least
--     one of @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ /must/ be
--     'Vulkan.Core10.APIConstants.QUEUE_FAMILY_IGNORED'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_sample_locations.SampleLocationsInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @oldLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @newLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @image@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @subresourceRange@ /must/ be a valid
--     'Vulkan.Core10.ImageView.ImageSubresourceRange' structure
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlags',
-- 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout',
-- 'Vulkan.Core10.ImageView.ImageSubresourceRange',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdPipelineBarrier',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWaitEvents'
data ImageMemoryBarrier (es :: [Type]) = ImageMemoryBarrier
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    ImageMemoryBarrier es -> Chain es
next :: Chain es
  , -- | @srcAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>.
    ImageMemoryBarrier es -> AccessFlags
srcAccessMask :: AccessFlags
  , -- | @dstAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>.
    ImageMemoryBarrier es -> AccessFlags
dstAccessMask :: AccessFlags
  , -- | @oldLayout@ is the old layout in an
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>.
    ImageMemoryBarrier es -> ImageLayout
oldLayout :: ImageLayout
  , -- | @newLayout@ is the new layout in an
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transition>.
    ImageMemoryBarrier es -> ImageLayout
newLayout :: ImageLayout
  , -- | @srcQueueFamilyIndex@ is the source queue family for a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>.
    ImageMemoryBarrier es -> Word32
srcQueueFamilyIndex :: Word32
  , -- | @dstQueueFamilyIndex@ is the destination queue family for a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>.
    ImageMemoryBarrier es -> Word32
dstQueueFamilyIndex :: Word32
  , -- | @image@ is a handle to the image affected by this barrier.
    ImageMemoryBarrier es -> Image
image :: Image
  , -- | @subresourceRange@ describes the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-views image subresource range>
    -- within @image@ that is affected by this barrier.
    ImageMemoryBarrier es -> ImageSubresourceRange
subresourceRange :: ImageSubresourceRange
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageMemoryBarrier (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (ImageMemoryBarrier es)

instance Extensible ImageMemoryBarrier where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER
  setNext :: ImageMemoryBarrier ds -> Chain es -> ImageMemoryBarrier es
setNext x :: ImageMemoryBarrier ds
x next :: Chain es
next = ImageMemoryBarrier ds
x{$sel:next:ImageMemoryBarrier :: Chain es
next = Chain es
next}
  getNext :: ImageMemoryBarrier es -> Chain es
getNext ImageMemoryBarrier{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends ImageMemoryBarrier e => b) -> Maybe b
  extends :: proxy e -> (Extends ImageMemoryBarrier e => b) -> Maybe b
extends _ f :: Extends ImageMemoryBarrier e => b
f
    | Just Refl <- (Typeable e, Typeable SampleLocationsInfoEXT) =>
Maybe (e :~: SampleLocationsInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SampleLocationsInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageMemoryBarrier e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss ImageMemoryBarrier es, PokeChain es) => ToCStruct (ImageMemoryBarrier es) where
  withCStruct :: ImageMemoryBarrier es
-> (Ptr (ImageMemoryBarrier es) -> IO b) -> IO b
withCStruct x :: ImageMemoryBarrier es
x f :: Ptr (ImageMemoryBarrier es) -> IO b
f = Int -> Int -> (Ptr (ImageMemoryBarrier es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr (ImageMemoryBarrier es) -> IO b) -> IO b)
-> (Ptr (ImageMemoryBarrier es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (ImageMemoryBarrier es)
p -> Ptr (ImageMemoryBarrier es)
-> ImageMemoryBarrier es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (ImageMemoryBarrier es)
p ImageMemoryBarrier es
x (Ptr (ImageMemoryBarrier es) -> IO b
f Ptr (ImageMemoryBarrier es)
p)
  pokeCStruct :: Ptr (ImageMemoryBarrier es)
-> ImageMemoryBarrier es -> IO b -> IO b
pokeCStruct p :: Ptr (ImageMemoryBarrier es)
p ImageMemoryBarrier{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageLayout)) (ImageLayout
oldLayout)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageLayout)) (ImageLayout
newLayout)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
srcQueueFamilyIndex)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) (Word32
dstQueueFamilyIndex)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Image)) (Image
image)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange
subresourceRange) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 72
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (ImageMemoryBarrier es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (ImageMemoryBarrier es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Image)) (Image
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss ImageMemoryBarrier es, PeekChain es) => FromCStruct (ImageMemoryBarrier es) where
  peekCStruct :: Ptr (ImageMemoryBarrier es) -> IO (ImageMemoryBarrier es)
peekCStruct p :: Ptr (ImageMemoryBarrier es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags))
    AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags))
    ImageLayout
oldLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageLayout))
    ImageLayout
newLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageLayout))
    Word32
srcQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Word32
dstQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32))
    Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Image))
    ImageSubresourceRange
subresourceRange <- Ptr ImageSubresourceRange -> IO ImageSubresourceRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceRange ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageSubresourceRange))
    ImageMemoryBarrier es -> IO (ImageMemoryBarrier es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageMemoryBarrier es -> IO (ImageMemoryBarrier es))
-> ImageMemoryBarrier es -> IO (ImageMemoryBarrier es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
forall (es :: [*]).
Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
ImageMemoryBarrier
             Chain es
next AccessFlags
srcAccessMask AccessFlags
dstAccessMask ImageLayout
oldLayout ImageLayout
newLayout Word32
srcQueueFamilyIndex Word32
dstQueueFamilyIndex Image
image ImageSubresourceRange
subresourceRange

instance es ~ '[] => Zero (ImageMemoryBarrier es) where
  zero :: ImageMemoryBarrier es
zero = Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
forall (es :: [*]).
Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
ImageMemoryBarrier
           ()
           AccessFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Image
forall a. Zero a => a
zero
           ImageSubresourceRange
forall a. Zero a => a
zero


-- | VkDrawIndirectCommand - Structure specifying a draw indirect command
--
-- = Description
--
-- The members of 'DrawIndirectCommand' have the same meaning as the
-- similarly named parameters of
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDraw'.
--
-- == Valid Usage
--
-- -   For a given vertex buffer binding, any attribute data fetched /must/
--     be entirely contained within the corresponding vertex buffer
--     binding, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input>
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-drawIndirectFirstInstance drawIndirectFirstInstance>
--     feature is not enabled, @firstInstance@ /must/ be @0@
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndirect'
data DrawIndirectCommand = DrawIndirectCommand
  { -- | @vertexCount@ is the number of vertices to draw.
    DrawIndirectCommand -> Word32
vertexCount :: Word32
  , -- | @instanceCount@ is the number of instances to draw.
    DrawIndirectCommand -> Word32
instanceCount :: Word32
  , -- | @firstVertex@ is the index of the first vertex to draw.
    DrawIndirectCommand -> Word32
firstVertex :: Word32
  , -- | @firstInstance@ is the instance ID of the first instance to draw.
    DrawIndirectCommand -> Word32
firstInstance :: Word32
  }
  deriving (Typeable, DrawIndirectCommand -> DrawIndirectCommand -> Bool
(DrawIndirectCommand -> DrawIndirectCommand -> Bool)
-> (DrawIndirectCommand -> DrawIndirectCommand -> Bool)
-> Eq DrawIndirectCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
$c/= :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
== :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
$c== :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrawIndirectCommand)
#endif
deriving instance Show DrawIndirectCommand

instance ToCStruct DrawIndirectCommand where
  withCStruct :: DrawIndirectCommand -> (Ptr DrawIndirectCommand -> IO b) -> IO b
withCStruct x :: DrawIndirectCommand
x f :: Ptr DrawIndirectCommand -> IO b
f = Int -> Int -> (Ptr DrawIndirectCommand -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr DrawIndirectCommand -> IO b) -> IO b)
-> (Ptr DrawIndirectCommand -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DrawIndirectCommand
p -> Ptr DrawIndirectCommand -> DrawIndirectCommand -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawIndirectCommand
p DrawIndirectCommand
x (Ptr DrawIndirectCommand -> IO b
f Ptr DrawIndirectCommand
p)
  pokeCStruct :: Ptr DrawIndirectCommand -> DrawIndirectCommand -> IO b -> IO b
pokeCStruct p :: Ptr DrawIndirectCommand
p DrawIndirectCommand{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
vertexCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
instanceCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
firstVertex)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
firstInstance)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr DrawIndirectCommand -> IO b -> IO b
pokeZeroCStruct p :: Ptr DrawIndirectCommand
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DrawIndirectCommand where
  peekCStruct :: Ptr DrawIndirectCommand -> IO DrawIndirectCommand
peekCStruct p :: Ptr DrawIndirectCommand
p = do
    Word32
vertexCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
instanceCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
firstVertex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Word32
firstInstance <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    DrawIndirectCommand -> IO DrawIndirectCommand
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DrawIndirectCommand -> IO DrawIndirectCommand)
-> DrawIndirectCommand -> IO DrawIndirectCommand
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Word32 -> Word32 -> DrawIndirectCommand
DrawIndirectCommand
             Word32
vertexCount Word32
instanceCount Word32
firstVertex Word32
firstInstance

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

instance Zero DrawIndirectCommand where
  zero :: DrawIndirectCommand
zero = Word32 -> Word32 -> Word32 -> Word32 -> DrawIndirectCommand
DrawIndirectCommand
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkDrawIndexedIndirectCommand - Structure specifying a draw indexed
-- indirect command
--
-- = Description
--
-- The members of 'DrawIndexedIndirectCommand' have the same meaning as the
-- similarly named parameters of
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexed'.
--
-- == Valid Usage
--
-- -   For a given vertex buffer binding, any attribute data fetched /must/
--     be entirely contained within the corresponding vertex buffer
--     binding, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input>
--
-- -   (@indexSize@ × (@firstIndex@ + @indexCount@) + @offset@) /must/ be
--     less than or equal to the size of the bound index buffer, with
--     @indexSize@ being based on the type specified by @indexType@, where
--     the index buffer, @indexType@, and @offset@ are specified via
--     'Vulkan.Core10.CommandBufferBuilding.cmdBindIndexBuffer'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-drawIndirectFirstInstance drawIndirectFirstInstance>
--     feature is not enabled, @firstInstance@ /must/ be @0@
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexedIndirect'
data DrawIndexedIndirectCommand = DrawIndexedIndirectCommand
  { -- | @indexCount@ is the number of vertices to draw.
    DrawIndexedIndirectCommand -> Word32
indexCount :: Word32
  , -- | @instanceCount@ is the number of instances to draw.
    DrawIndexedIndirectCommand -> Word32
instanceCount :: Word32
  , -- | @firstIndex@ is the base index within the index buffer.
    DrawIndexedIndirectCommand -> Word32
firstIndex :: Word32
  , -- | @vertexOffset@ is the value added to the vertex index before indexing
    -- into the vertex buffer.
    DrawIndexedIndirectCommand -> Int32
vertexOffset :: Int32
  , -- | @firstInstance@ is the instance ID of the first instance to draw.
    DrawIndexedIndirectCommand -> Word32
firstInstance :: Word32
  }
  deriving (Typeable, DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
(DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool)
-> (DrawIndexedIndirectCommand
    -> DrawIndexedIndirectCommand -> Bool)
-> Eq DrawIndexedIndirectCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
$c/= :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
== :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
$c== :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrawIndexedIndirectCommand)
#endif
deriving instance Show DrawIndexedIndirectCommand

instance ToCStruct DrawIndexedIndirectCommand where
  withCStruct :: DrawIndexedIndirectCommand
-> (Ptr DrawIndexedIndirectCommand -> IO b) -> IO b
withCStruct x :: DrawIndexedIndirectCommand
x f :: Ptr DrawIndexedIndirectCommand -> IO b
f = Int -> Int -> (Ptr DrawIndexedIndirectCommand -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 20 4 ((Ptr DrawIndexedIndirectCommand -> IO b) -> IO b)
-> (Ptr DrawIndexedIndirectCommand -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DrawIndexedIndirectCommand
p -> Ptr DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawIndexedIndirectCommand
p DrawIndexedIndirectCommand
x (Ptr DrawIndexedIndirectCommand -> IO b
f Ptr DrawIndexedIndirectCommand
p)
  pokeCStruct :: Ptr DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> IO b -> IO b
pokeCStruct p :: Ptr DrawIndexedIndirectCommand
p DrawIndexedIndirectCommand{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
indexCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
instanceCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
firstIndex)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Int32)) (Int32
vertexOffset)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
firstInstance)
    IO b
f
  cStructSize :: Int
cStructSize = 20
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr DrawIndexedIndirectCommand -> IO b -> IO b
pokeZeroCStruct p :: Ptr DrawIndexedIndirectCommand
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DrawIndexedIndirectCommand where
  peekCStruct :: Ptr DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
peekCStruct p :: Ptr DrawIndexedIndirectCommand
p = do
    Word32
indexCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
instanceCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
firstIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Int32
vertexOffset <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Int32))
    Word32
firstInstance <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand)
-> DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> Int32
-> Word32
-> DrawIndexedIndirectCommand
DrawIndexedIndirectCommand
             Word32
indexCount Word32
instanceCount Word32
firstIndex Int32
vertexOffset Word32
firstInstance

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

instance Zero DrawIndexedIndirectCommand where
  zero :: DrawIndexedIndirectCommand
zero = Word32
-> Word32
-> Word32
-> Int32
-> Word32
-> DrawIndexedIndirectCommand
DrawIndexedIndirectCommand
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkDispatchIndirectCommand - Structure specifying a dispatch indirect
-- command
--
-- = Description
--
-- The members of 'DispatchIndirectCommand' have the same meaning as the
-- corresponding parameters of
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatch'.
--
-- == Valid Usage
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatchIndirect'
data DispatchIndirectCommand = DispatchIndirectCommand
  { -- | @x@ is the number of local workgroups to dispatch in the X dimension.
    --
    -- @x@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0]
    DispatchIndirectCommand -> Word32
x :: Word32
  , -- | @y@ is the number of local workgroups to dispatch in the Y dimension.
    --
    -- @y@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1]
    DispatchIndirectCommand -> Word32
y :: Word32
  , -- | @z@ is the number of local workgroups to dispatch in the Z dimension.
    --
    -- @z@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2]
    DispatchIndirectCommand -> Word32
z :: Word32
  }
  deriving (Typeable, DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
(DispatchIndirectCommand -> DispatchIndirectCommand -> Bool)
-> (DispatchIndirectCommand -> DispatchIndirectCommand -> Bool)
-> Eq DispatchIndirectCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
$c/= :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
== :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
$c== :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DispatchIndirectCommand)
#endif
deriving instance Show DispatchIndirectCommand

instance ToCStruct DispatchIndirectCommand where
  withCStruct :: DispatchIndirectCommand
-> (Ptr DispatchIndirectCommand -> IO b) -> IO b
withCStruct x :: DispatchIndirectCommand
x f :: Ptr DispatchIndirectCommand -> IO b
f = Int -> Int -> (Ptr DispatchIndirectCommand -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((Ptr DispatchIndirectCommand -> IO b) -> IO b)
-> (Ptr DispatchIndirectCommand -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DispatchIndirectCommand
p -> Ptr DispatchIndirectCommand
-> DispatchIndirectCommand -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DispatchIndirectCommand
p DispatchIndirectCommand
x (Ptr DispatchIndirectCommand -> IO b
f Ptr DispatchIndirectCommand
p)
  pokeCStruct :: Ptr DispatchIndirectCommand
-> DispatchIndirectCommand -> IO b -> IO b
pokeCStruct p :: Ptr DispatchIndirectCommand
p DispatchIndirectCommand{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
x)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
y)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
z)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr DispatchIndirectCommand -> IO b -> IO b
pokeZeroCStruct p :: Ptr DispatchIndirectCommand
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DispatchIndirectCommand where
  peekCStruct :: Ptr DispatchIndirectCommand -> IO DispatchIndirectCommand
peekCStruct p :: Ptr DispatchIndirectCommand
p = do
    Word32
x <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
y <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
z <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    DispatchIndirectCommand -> IO DispatchIndirectCommand
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DispatchIndirectCommand -> IO DispatchIndirectCommand)
-> DispatchIndirectCommand -> IO DispatchIndirectCommand
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Word32 -> DispatchIndirectCommand
DispatchIndirectCommand
             Word32
x Word32
y Word32
z

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

instance Zero DispatchIndirectCommand where
  zero :: DispatchIndirectCommand
zero = Word32 -> Word32 -> Word32 -> DispatchIndirectCommand
DispatchIndirectCommand
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero