{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_device_group  ( getDeviceGroupPeerMemoryFeatures
                                                        , cmdSetDeviceMask
                                                        , cmdDispatchBase
                                                        , pattern PIPELINE_CREATE_DISPATCH_BASE
                                                        , MemoryAllocateFlagsInfo(..)
                                                        , DeviceGroupRenderPassBeginInfo(..)
                                                        , DeviceGroupCommandBufferBeginInfo(..)
                                                        , DeviceGroupSubmitInfo(..)
                                                        , DeviceGroupBindSparseInfo(..)
                                                        , StructureType(..)
                                                        , PipelineCreateFlagBits(..)
                                                        , PipelineCreateFlags
                                                        , DependencyFlagBits(..)
                                                        , DependencyFlags
                                                        , PeerMemoryFeatureFlagBits(..)
                                                        , PeerMemoryFeatureFlags
                                                        , MemoryAllocateFlagBits(..)
                                                        , MemoryAllocateFlags
                                                        ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDispatchBase))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDeviceMask))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceGroupPeerMemoryFeatures))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlags)
import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlagBits(..))
import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlags)
import Vulkan.Core10.FundamentalTypes (Rect2D)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags)
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlagBits(PIPELINE_CREATE_DISPATCH_BASE_BIT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO))
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlagBits(..))
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags)
import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlagBits(..))
import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlags)
import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlagBits(..))
import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlags)
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlagBits(..))
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceGroupPeerMemoryFeatures
  :: FunPtr (Ptr Device_T -> Word32 -> Word32 -> Word32 -> Ptr PeerMemoryFeatureFlags -> IO ()) -> Ptr Device_T -> Word32 -> Word32 -> Word32 -> Ptr PeerMemoryFeatureFlags -> IO ()

-- | vkGetDeviceGroupPeerMemoryFeatures - Query supported peer memory
-- features of a device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits.PeerMemoryFeatureFlags'
getDeviceGroupPeerMemoryFeatures :: forall io
                                  . (MonadIO io)
                                 => -- | @device@ is the logical device that owns the memory.
                                    --
                                    -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                    Device
                                 -> -- | @heapIndex@ is the index of the memory heap from which the memory is
                                    -- allocated.
                                    --
                                    -- @heapIndex@ /must/ be less than @memoryHeapCount@
                                    ("heapIndex" ::: Word32)
                                 -> -- | @localDeviceIndex@ is the device index of the physical device that
                                    -- performs the memory access.
                                    --
                                    -- @localDeviceIndex@ /must/ be a valid device index
                                    --
                                    -- @localDeviceIndex@ /must/ not equal @remoteDeviceIndex@
                                    ("localDeviceIndex" ::: Word32)
                                 -> -- | @remoteDeviceIndex@ is the device index of the physical device that the
                                    -- memory is allocated for.
                                    --
                                    -- @remoteDeviceIndex@ /must/ be a valid device index
                                    ("remoteDeviceIndex" ::: Word32)
                                 -> io (("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
getDeviceGroupPeerMemoryFeatures :: Device
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
getDeviceGroupPeerMemoryFeatures device :: Device
device heapIndex :: "heapIndex" ::: Word32
heapIndex localDeviceIndex :: "heapIndex" ::: Word32
localDeviceIndex remoteDeviceIndex :: "heapIndex" ::: Word32
remoteDeviceIndex = IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
 -> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> (ContT
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
      IO
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
    -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
  IO
  ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
   IO
   ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
 -> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeviceGroupPeerMemoryFeaturesPtr :: FunPtr
  (Ptr Device_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ())
vkGetDeviceGroupPeerMemoryFeaturesPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("pPeerMemoryFeatures"
          ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
      -> IO ())
pVkGetDeviceGroupPeerMemoryFeatures (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO ()
-> ContT ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) IO ())
-> IO ()
-> ContT ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ())
vkGetDeviceGroupPeerMemoryFeaturesPtr FunPtr
  (Ptr Device_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("pPeerMemoryFeatures"
          ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetDeviceGroupPeerMemoryFeatures is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceGroupPeerMemoryFeatures' :: Ptr Device_T
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("pPeerMemoryFeatures"
    ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ()
vkGetDeviceGroupPeerMemoryFeatures' = FunPtr
  (Ptr Device_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ())
-> Ptr Device_T
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("pPeerMemoryFeatures"
    ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ()
mkVkGetDeviceGroupPeerMemoryFeatures FunPtr
  (Ptr Device_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ())
vkGetDeviceGroupPeerMemoryFeaturesPtr
  "pPeerMemoryFeatures"
::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
pPPeerMemoryFeatures <- ((("pPeerMemoryFeatures"
   ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
  -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
 -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("pPeerMemoryFeatures"
      ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPeerMemoryFeatures"
    ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
   -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
  -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
 -> ContT
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
      IO
      ("pPeerMemoryFeatures"
       ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)))
-> ((("pPeerMemoryFeatures"
      ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
     -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
    -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("pPeerMemoryFeatures"
      ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
forall a b. (a -> b) -> a -> b
$ IO
  ("pPeerMemoryFeatures"
   ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> (("pPeerMemoryFeatures"
     ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
    -> IO ())
-> (("pPeerMemoryFeatures"
     ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
    -> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO
     ("pPeerMemoryFeatures"
      ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
forall a. Int -> IO (Ptr a)
callocBytes @PeerMemoryFeatureFlags 4) ("pPeerMemoryFeatures"
 ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ()
forall a. Ptr a -> IO ()
free
  IO ()
-> ContT ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) IO ())
-> IO ()
-> ContT ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("pPeerMemoryFeatures"
    ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ()
vkGetDeviceGroupPeerMemoryFeatures' (Device -> Ptr Device_T
deviceHandle (Device
device)) ("heapIndex" ::: Word32
heapIndex) ("heapIndex" ::: Word32
localDeviceIndex) ("heapIndex" ::: Word32
remoteDeviceIndex) ("pPeerMemoryFeatures"
::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
pPPeerMemoryFeatures)
  "peerMemoryFeatures" ::: PeerMemoryFeatureFlags
pPeerMemoryFeatures <- IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
 -> ContT
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
      IO
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall a b. (a -> b) -> a -> b
$ ("pPeerMemoryFeatures"
 ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> IO ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall a. Storable a => Ptr a -> IO a
peek @PeerMemoryFeatureFlags "pPeerMemoryFeatures"
::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
pPPeerMemoryFeatures
  ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
 -> ContT
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
      IO
      ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags))
-> ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
-> ContT
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
     IO
     ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)
forall a b. (a -> b) -> a -> b
$ ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags
pPeerMemoryFeatures)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetDeviceMask
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> IO ()

-- | vkCmdSetDeviceMask - Modify device mask of a command buffer
--
-- = Description
--
-- @deviceMask@ is used to filter out subsequent commands from executing on
-- all physical devices whose bit indices are not set in the mask, except
-- commands beginning a render pass instance, commands transitioning to the
-- next subpass in the render pass instance, and commands ending a render
-- pass instance, which always execute on the set of physical devices whose
-- bit indices are included in the @deviceMask@ member of the
-- 'DeviceGroupRenderPassBeginInfo' structure passed to the command
-- beginning the corresponding render pass instance.
--
-- == Valid Usage
--
-- -   @deviceMask@ /must/ be a valid device mask value
--
-- -   @deviceMask@ /must/ not be zero
--
-- -   @deviceMask@ /must/ not include any set bits that were not in the
--     'DeviceGroupCommandBufferBeginInfo'::@deviceMask@ value when the
--     command buffer began recording
--
-- -   If 'cmdSetDeviceMask' is called inside a render pass instance,
--     @deviceMask@ /must/ not include any set bits that were not in the
--     'DeviceGroupRenderPassBeginInfo'::@deviceMask@ value when the render
--     pass instance began recording
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, compute, or transfer
--     operations
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Transfer                                                                                                              |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDeviceMask :: forall io
                  . (MonadIO io)
                 => -- | @commandBuffer@ is command buffer whose current device mask is modified.
                    CommandBuffer
                 -> -- | @deviceMask@ is the new value of the current device mask.
                    ("deviceMask" ::: Word32)
                 -> io ()
cmdSetDeviceMask :: CommandBuffer -> ("heapIndex" ::: Word32) -> io ()
cmdSetDeviceMask commandBuffer :: CommandBuffer
commandBuffer deviceMask :: "heapIndex" ::: Word32
deviceMask = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetDeviceMaskPtr :: FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
vkCmdSetDeviceMaskPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
pVkCmdSetDeviceMask (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
vkCmdSetDeviceMaskPtr FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCmdSetDeviceMask is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetDeviceMask' :: Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()
vkCmdSetDeviceMask' = FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
-> Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()
mkVkCmdSetDeviceMask FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ())
vkCmdSetDeviceMaskPtr
  Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()
vkCmdSetDeviceMask' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("heapIndex" ::: Word32
deviceMask)
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDispatchBase
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> IO ()

-- | vkCmdDispatchBase - Dispatch compute work items
--
-- = Description
--
-- When the command is executed, a global workgroup consisting of
-- @groupCountX@ × @groupCountY@ × @groupCountZ@ local workgroups is
-- assembled, with @WorkgroupId@ values ranging from [@baseGroup*@,
-- @baseGroup*@ + @groupCount*@) in each component.
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatch' is equivalent to
-- @vkCmdDispatchBase(0,0,0,groupCountX,groupCountY,groupCountZ)@.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is sampled with
--     'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' as a result of this
--     command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic
--     operations as a result of this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT'
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result
--     of this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT'
--
-- -   Any 'Vulkan.Core10.Handles.ImageView' being sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result
--     of this command /must/ have a
--     'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that
--     supports cubic filtering, as specified by
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@
--     returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
--
-- -   Any 'Vulkan.Core10.Handles.ImageView' being sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a
--     reduction mode of either
--     'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN'
--     or
--     'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX'
--     as a result of this command /must/ have a
--     'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that
--     supports cubic filtering together with minmax filtering, as
--     specified by
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@
--     returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
--
-- -   Any 'Vulkan.Core10.Handles.Image' created with a
--     'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV'
--     sampled as a result of this command /must/ only be sampled using a
--     'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of
--     'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE'
--
-- -   For each set /n/ that is statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command, a descriptor set /must/ have been bound to /n/
--     at the same pipeline bind point, with a
--     'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set
--     /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create
--     the current 'Vulkan.Core10.Handles.Pipeline', as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???>
--
-- -   For each push constant that is statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command, a push constant value /must/ have been set for
--     the same pipeline bind point, with a
--     'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push
--     constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to
--     create the current 'Vulkan.Core10.Handles.Pipeline', as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???>
--
-- -   Descriptors in each bound descriptor set, specified via
--     'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets', /must/
--     be valid if they are statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command
--
-- -   A valid pipeline /must/ be bound to the pipeline bind point used by
--     this command
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command requires any dynamic state, that
--     state /must/ have been set for @commandBuffer@, and done so after
--     any previously bound pipeline with the corresponding state not
--     specified as dynamic
--
-- -   There /must/ not have been any calls to dynamic state setting
--     commands for any state not specified as dynamic in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point used by this command, since that pipeline was bound
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used to sample from any
--     'Vulkan.Core10.Handles.Image' with a
--     'Vulkan.Core10.Handles.ImageView' of the type
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in
--     any shader stage
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used with any of the SPIR-V
--     @OpImageSample*@ or @OpImageSparseSample*@ instructions with
--     @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used with any of the SPIR-V
--     @OpImageSample*@ or @OpImageSparseSample*@ instructions that
--     includes a LOD bias or any offset values, in any shader stage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access>
--     feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline'
--     object bound to the pipeline bind point used by this command
--     accesses a uniform buffer, it /must/ not access values outside of
--     the range of the buffer as specified in the descriptor set bound to
--     the same pipeline bind point
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access>
--     feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline'
--     object bound to the pipeline bind point used by this command
--     accesses a storage buffer, it /must/ not access values outside of
--     the range of the buffer as specified in the descriptor set bound to
--     the same pipeline bind point
--
-- -   If @commandBuffer@ is an unprotected command buffer, any resource
--     accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the
--     pipeline bind point used by this command /must/ not be a protected
--     resource
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is accessed using
--     @OpImageWrite@ as a result of this command, then the @Type@ of the
--     @Texel@ operand of that instruction /must/ have at least as many
--     components as the image view’s format.
--
-- -   @baseGroupX@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0]
--
-- -   @baseGroupX@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1]
--
-- -   @baseGroupZ@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2]
--
-- -   @groupCountX@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0]
--     minus @baseGroupX@
--
-- -   @groupCountY@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1]
--     minus @baseGroupY@
--
-- -   @groupCountZ@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2]
--     minus @baseGroupZ@
--
-- -   If any of @baseGroupX@, @baseGroupY@, or @baseGroupZ@ are not zero,
--     then the bound compute pipeline /must/ have been created with the
--     'PIPELINE_CREATE_DISPATCH_BASE' flag
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdDispatchBase :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command will be
                   -- recorded.
                   CommandBuffer
                -> -- | @baseGroupX@ is the start value for the X component of @WorkgroupId@.
                   ("baseGroupX" ::: Word32)
                -> -- | @baseGroupY@ is the start value for the Y component of @WorkgroupId@.
                   ("baseGroupY" ::: Word32)
                -> -- | @baseGroupZ@ is the start value for the Z component of @WorkgroupId@.
                   ("baseGroupZ" ::: Word32)
                -> -- | @groupCountX@ is the number of local workgroups to dispatch in the X
                   -- dimension.
                   ("groupCountX" ::: Word32)
                -> -- | @groupCountY@ is the number of local workgroups to dispatch in the Y
                   -- dimension.
                   ("groupCountY" ::: Word32)
                -> -- | @groupCountZ@ is the number of local workgroups to dispatch in the Z
                   -- dimension.
                   ("groupCountZ" ::: Word32)
                -> io ()
cmdDispatchBase :: CommandBuffer
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> io ()
cmdDispatchBase commandBuffer :: CommandBuffer
commandBuffer baseGroupX :: "heapIndex" ::: Word32
baseGroupX baseGroupY :: "heapIndex" ::: Word32
baseGroupY baseGroupZ :: "heapIndex" ::: Word32
baseGroupZ groupCountX :: "heapIndex" ::: Word32
groupCountX groupCountY :: "heapIndex" ::: Word32
groupCountY groupCountZ :: "heapIndex" ::: Word32
groupCountZ = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDispatchBasePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> IO ())
vkCmdDispatchBasePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> IO ())
pVkCmdDispatchBase (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> IO ())
vkCmdDispatchBasePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> ("heapIndex" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCmdDispatchBase is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDispatchBase' :: Ptr CommandBuffer_T
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> IO ()
vkCmdDispatchBase' = FunPtr
  (Ptr CommandBuffer_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> IO ()
mkVkCmdDispatchBase FunPtr
  (Ptr CommandBuffer_T
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> ("heapIndex" ::: Word32)
   -> IO ())
vkCmdDispatchBasePtr
  Ptr CommandBuffer_T
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32)
-> IO ()
vkCmdDispatchBase' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("heapIndex" ::: Word32
baseGroupX) ("heapIndex" ::: Word32
baseGroupY) ("heapIndex" ::: Word32
baseGroupZ) ("heapIndex" ::: Word32
groupCountX) ("heapIndex" ::: Word32
groupCountY) ("heapIndex" ::: Word32
groupCountZ)
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- No documentation found for TopLevel "VK_PIPELINE_CREATE_DISPATCH_BASE"
pattern $bPIPELINE_CREATE_DISPATCH_BASE :: PipelineCreateFlagBits
$mPIPELINE_CREATE_DISPATCH_BASE :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_DISPATCH_BASE = PIPELINE_CREATE_DISPATCH_BASE_BIT


-- | VkMemoryAllocateFlagsInfo - Structure controlling how many instances of
-- memory will be allocated
--
-- = Description
--
-- If
-- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT'
-- is not set, the number of instances allocated depends on whether
-- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_MULTI_INSTANCE_BIT'
-- is set in the memory heap. If
-- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_MULTI_INSTANCE_BIT'
-- is set, then memory is allocated for every physical device in the
-- logical device (as if @deviceMask@ has bits set for all device indices).
-- If
-- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_MULTI_INSTANCE_BIT'
-- is not set, then a single instance of memory is allocated (as if
-- @deviceMask@ is set to one).
--
-- On some implementations, allocations from a multi-instance heap /may/
-- consume memory on all physical devices even if the @deviceMask@ excludes
-- some devices. If
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.PhysicalDeviceGroupProperties'::@subsetAllocation@
-- is 'Vulkan.Core10.FundamentalTypes.TRUE', then memory is only consumed
-- for the devices in the device mask.
--
-- Note
--
-- In practice, most allocations on a multi-instance heap will be allocated
-- across all physical devices. Unicast allocation support is an optional
-- optimization for a minority of allocations.
--
-- == Valid Usage
--
-- -   If
--     'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT'
--     is set, @deviceMask@ /must/ be a valid device mask
--
-- -   If
--     'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT'
--     is set, @deviceMask@ /must/ not be zero
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO'
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MemoryAllocateFlagBits'
--     values
--
-- = See Also
--
-- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MemoryAllocateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data MemoryAllocateFlagsInfo = MemoryAllocateFlagsInfo
  { -- | @flags@ is a bitmask of
    -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MemoryAllocateFlagBits'
    -- controlling the allocation.
    MemoryAllocateFlagsInfo -> MemoryAllocateFlags
flags :: MemoryAllocateFlags
  , -- | @deviceMask@ is a mask of physical devices in the logical device,
    -- indicating that memory /must/ be allocated on each device in the mask,
    -- if
    -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT'
    -- is set in @flags@.
    MemoryAllocateFlagsInfo -> "heapIndex" ::: Word32
deviceMask :: Word32
  }
  deriving (Typeable, MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool
(MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool)
-> (MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool)
-> Eq MemoryAllocateFlagsInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool
$c/= :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool
== :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool
$c== :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryAllocateFlagsInfo)
#endif
deriving instance Show MemoryAllocateFlagsInfo

instance ToCStruct MemoryAllocateFlagsInfo where
  withCStruct :: MemoryAllocateFlagsInfo
-> (Ptr MemoryAllocateFlagsInfo -> IO b) -> IO b
withCStruct x :: MemoryAllocateFlagsInfo
x f :: Ptr MemoryAllocateFlagsInfo -> IO b
f = Int -> Int -> (Ptr MemoryAllocateFlagsInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr MemoryAllocateFlagsInfo -> IO b) -> IO b)
-> (Ptr MemoryAllocateFlagsInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryAllocateFlagsInfo
p -> Ptr MemoryAllocateFlagsInfo
-> MemoryAllocateFlagsInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryAllocateFlagsInfo
p MemoryAllocateFlagsInfo
x (Ptr MemoryAllocateFlagsInfo -> IO b
f Ptr MemoryAllocateFlagsInfo
p)
  pokeCStruct :: Ptr MemoryAllocateFlagsInfo
-> MemoryAllocateFlagsInfo -> IO b -> IO b
pokeCStruct p :: Ptr MemoryAllocateFlagsInfo
p MemoryAllocateFlagsInfo{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr MemoryAllocateFlags -> MemoryAllocateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr MemoryAllocateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr MemoryAllocateFlags)) (MemoryAllocateFlags
flags)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("heapIndex" ::: Word32
deviceMask)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr MemoryAllocateFlagsInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryAllocateFlagsInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("heapIndex" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MemoryAllocateFlagsInfo where
  peekCStruct :: Ptr MemoryAllocateFlagsInfo -> IO MemoryAllocateFlagsInfo
peekCStruct p :: Ptr MemoryAllocateFlagsInfo
p = do
    MemoryAllocateFlags
flags <- Ptr MemoryAllocateFlags -> IO MemoryAllocateFlags
forall a. Storable a => Ptr a -> IO a
peek @MemoryAllocateFlags ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr MemoryAllocateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr MemoryAllocateFlags))
    "heapIndex" ::: Word32
deviceMask <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr MemoryAllocateFlagsInfo
p Ptr MemoryAllocateFlagsInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    MemoryAllocateFlagsInfo -> IO MemoryAllocateFlagsInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryAllocateFlagsInfo -> IO MemoryAllocateFlagsInfo)
-> MemoryAllocateFlagsInfo -> IO MemoryAllocateFlagsInfo
forall a b. (a -> b) -> a -> b
$ MemoryAllocateFlags
-> ("heapIndex" ::: Word32) -> MemoryAllocateFlagsInfo
MemoryAllocateFlagsInfo
             MemoryAllocateFlags
flags "heapIndex" ::: Word32
deviceMask

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

instance Zero MemoryAllocateFlagsInfo where
  zero :: MemoryAllocateFlagsInfo
zero = MemoryAllocateFlags
-> ("heapIndex" ::: Word32) -> MemoryAllocateFlagsInfo
MemoryAllocateFlagsInfo
           MemoryAllocateFlags
forall a. Zero a => a
zero
           "heapIndex" ::: Word32
forall a. Zero a => a
zero


-- | VkDeviceGroupRenderPassBeginInfo - Set the initial device mask and
-- render areas for a render pass instance
--
-- = Description
--
-- The @deviceMask@ serves several purposes. It is an upper bound on the
-- set of physical devices that /can/ be used during the render pass
-- instance, and the initial device mask when the render pass instance
-- begins. In addition, commands transitioning to the next subpass in the
-- render pass instance and commands ending the render pass instance, and,
-- accordingly render pass attachment load, store, and resolve operations
-- and subpass dependencies corresponding to the render pass instance, are
-- executed on the physical devices included in the device mask provided
-- here.
--
-- If @deviceRenderAreaCount@ is not zero, then the elements of
-- @pDeviceRenderAreas@ override the value of
-- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'::@renderArea@,
-- and provide a render area specific to each physical device. These render
-- areas serve the same purpose as
-- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'::@renderArea@,
-- including controlling the region of attachments that are cleared by
-- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' and that
-- are resolved into resolve attachments.
--
-- If this structure is not present, the render pass instance’s device mask
-- is the value of 'DeviceGroupCommandBufferBeginInfo'::@deviceMask@. If
-- this structure is not present or if @deviceRenderAreaCount@ is zero,
-- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'::@renderArea@
-- is used for all physical devices.
--
-- == Valid Usage
--
-- -   @deviceMask@ /must/ be a valid device mask value
--
-- -   @deviceMask@ /must/ not be zero
--
-- -   @deviceMask@ /must/ be a subset of the command buffer’s initial
--     device mask
--
-- -   @deviceRenderAreaCount@ /must/ either be zero or equal to the number
--     of physical devices in the logical device
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO'
--
-- -   If @deviceRenderAreaCount@ is not @0@, @pDeviceRenderAreas@ /must/
--     be a valid pointer to an array of @deviceRenderAreaCount@
--     'Vulkan.Core10.FundamentalTypes.Rect2D' structures
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Rect2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceGroupRenderPassBeginInfo = DeviceGroupRenderPassBeginInfo
  { -- | @deviceMask@ is the device mask for the render pass instance.
    DeviceGroupRenderPassBeginInfo -> "heapIndex" ::: Word32
deviceMask :: Word32
  , -- | @pDeviceRenderAreas@ is a pointer to an array of
    -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining the render
    -- area for each physical device.
    DeviceGroupRenderPassBeginInfo -> Vector Rect2D
deviceRenderAreas :: Vector Rect2D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupRenderPassBeginInfo)
#endif
deriving instance Show DeviceGroupRenderPassBeginInfo

instance ToCStruct DeviceGroupRenderPassBeginInfo where
  withCStruct :: DeviceGroupRenderPassBeginInfo
-> (Ptr DeviceGroupRenderPassBeginInfo -> IO b) -> IO b
withCStruct x :: DeviceGroupRenderPassBeginInfo
x f :: Ptr DeviceGroupRenderPassBeginInfo -> IO b
f = Int -> Int -> (Ptr DeviceGroupRenderPassBeginInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr DeviceGroupRenderPassBeginInfo -> IO b) -> IO b)
-> (Ptr DeviceGroupRenderPassBeginInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceGroupRenderPassBeginInfo
p -> Ptr DeviceGroupRenderPassBeginInfo
-> DeviceGroupRenderPassBeginInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceGroupRenderPassBeginInfo
p DeviceGroupRenderPassBeginInfo
x (Ptr DeviceGroupRenderPassBeginInfo -> IO b
f Ptr DeviceGroupRenderPassBeginInfo
p)
  pokeCStruct :: Ptr DeviceGroupRenderPassBeginInfo
-> DeviceGroupRenderPassBeginInfo -> IO b -> IO b
pokeCStruct p :: Ptr DeviceGroupRenderPassBeginInfo
p DeviceGroupRenderPassBeginInfo{..} 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 DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO)
    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 DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    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 ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("heapIndex" ::: Word32
deviceMask)
    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 ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> "heapIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Rect2D -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Rect2D -> Int) -> Vector Rect2D -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Rect2D
deviceRenderAreas)) :: Word32))
    Ptr Rect2D
pPDeviceRenderAreas' <- ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D))
-> ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Rect2D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D ((Vector Rect2D -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Rect2D
deviceRenderAreas)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> Rect2D -> ContT b IO ()) -> Vector Rect2D -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> 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 Rect2D -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Rect2D
pPDeviceRenderAreas' Ptr Rect2D -> Int -> Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e) (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
$ ())) (Vector Rect2D
deviceRenderAreas)
    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 Rect2D) -> Ptr Rect2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Rect2D))) (Ptr Rect2D
pPDeviceRenderAreas')
    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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeviceGroupRenderPassBeginInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceGroupRenderPassBeginInfo
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 DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO)
    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 DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    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 ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("heapIndex" ::: Word32
forall a. Zero a => a
zero)
    Ptr Rect2D
pPDeviceRenderAreas' <- ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D))
-> ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Rect2D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> Rect2D -> ContT b IO ()) -> Vector Rect2D -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> 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 Rect2D -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Rect2D
pPDeviceRenderAreas' Ptr Rect2D -> Int -> Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e) (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
$ ())) (Vector Rect2D
forall a. Monoid a => a
mempty)
    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 Rect2D) -> Ptr Rect2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Rect2D))) (Ptr Rect2D
pPDeviceRenderAreas')
    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 FromCStruct DeviceGroupRenderPassBeginInfo where
  peekCStruct :: Ptr DeviceGroupRenderPassBeginInfo
-> IO DeviceGroupRenderPassBeginInfo
peekCStruct p :: Ptr DeviceGroupRenderPassBeginInfo
p = do
    "heapIndex" ::: Word32
deviceMask <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "heapIndex" ::: Word32
deviceRenderAreaCount <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr Rect2D
pDeviceRenderAreas <- Ptr (Ptr Rect2D) -> IO (Ptr Rect2D)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Rect2D) ((Ptr DeviceGroupRenderPassBeginInfo
p Ptr DeviceGroupRenderPassBeginInfo -> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Rect2D)))
    Vector Rect2D
pDeviceRenderAreas' <- Int -> (Int -> IO Rect2D) -> IO (Vector Rect2D)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("heapIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "heapIndex" ::: Word32
deviceRenderAreaCount) (\i :: Int
i -> Ptr Rect2D -> IO Rect2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Rect2D ((Ptr Rect2D
pDeviceRenderAreas Ptr Rect2D -> Int -> Ptr Rect2D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D)))
    DeviceGroupRenderPassBeginInfo -> IO DeviceGroupRenderPassBeginInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupRenderPassBeginInfo
 -> IO DeviceGroupRenderPassBeginInfo)
-> DeviceGroupRenderPassBeginInfo
-> IO DeviceGroupRenderPassBeginInfo
forall a b. (a -> b) -> a -> b
$ ("heapIndex" ::: Word32)
-> Vector Rect2D -> DeviceGroupRenderPassBeginInfo
DeviceGroupRenderPassBeginInfo
             "heapIndex" ::: Word32
deviceMask Vector Rect2D
pDeviceRenderAreas'

instance Zero DeviceGroupRenderPassBeginInfo where
  zero :: DeviceGroupRenderPassBeginInfo
zero = ("heapIndex" ::: Word32)
-> Vector Rect2D -> DeviceGroupRenderPassBeginInfo
DeviceGroupRenderPassBeginInfo
           "heapIndex" ::: Word32
forall a. Zero a => a
zero
           Vector Rect2D
forall a. Monoid a => a
mempty


-- | VkDeviceGroupCommandBufferBeginInfo - Set the initial device mask for a
-- command buffer
--
-- = Description
--
-- The initial device mask also acts as an upper bound on the set of
-- devices that /can/ ever be in the device mask in the command buffer.
--
-- If this structure is not present, the initial value of a command
-- buffer’s device mask is set to include all physical devices in the
-- logical device when the command buffer begins recording.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceGroupCommandBufferBeginInfo = DeviceGroupCommandBufferBeginInfo
  { -- | @deviceMask@ is the initial value of the command buffer’s device mask.
    --
    -- @deviceMask@ /must/ be a valid device mask value
    --
    -- @deviceMask@ /must/ not be zero
    DeviceGroupCommandBufferBeginInfo -> "heapIndex" ::: Word32
deviceMask :: Word32 }
  deriving (Typeable, DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> Bool
(DeviceGroupCommandBufferBeginInfo
 -> DeviceGroupCommandBufferBeginInfo -> Bool)
-> (DeviceGroupCommandBufferBeginInfo
    -> DeviceGroupCommandBufferBeginInfo -> Bool)
-> Eq DeviceGroupCommandBufferBeginInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> Bool
$c/= :: DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> Bool
== :: DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> Bool
$c== :: DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupCommandBufferBeginInfo)
#endif
deriving instance Show DeviceGroupCommandBufferBeginInfo

instance ToCStruct DeviceGroupCommandBufferBeginInfo where
  withCStruct :: DeviceGroupCommandBufferBeginInfo
-> (Ptr DeviceGroupCommandBufferBeginInfo -> IO b) -> IO b
withCStruct x :: DeviceGroupCommandBufferBeginInfo
x f :: Ptr DeviceGroupCommandBufferBeginInfo -> IO b
f = Int
-> Int -> (Ptr DeviceGroupCommandBufferBeginInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DeviceGroupCommandBufferBeginInfo -> IO b) -> IO b)
-> (Ptr DeviceGroupCommandBufferBeginInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceGroupCommandBufferBeginInfo
p -> Ptr DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceGroupCommandBufferBeginInfo
p DeviceGroupCommandBufferBeginInfo
x (Ptr DeviceGroupCommandBufferBeginInfo -> IO b
f Ptr DeviceGroupCommandBufferBeginInfo
p)
  pokeCStruct :: Ptr DeviceGroupCommandBufferBeginInfo
-> DeviceGroupCommandBufferBeginInfo -> IO b -> IO b
pokeCStruct p :: Ptr DeviceGroupCommandBufferBeginInfo
p DeviceGroupCommandBufferBeginInfo{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("heapIndex" ::: Word32
deviceMask)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeviceGroupCommandBufferBeginInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceGroupCommandBufferBeginInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("heapIndex" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DeviceGroupCommandBufferBeginInfo where
  peekCStruct :: Ptr DeviceGroupCommandBufferBeginInfo
-> IO DeviceGroupCommandBufferBeginInfo
peekCStruct p :: Ptr DeviceGroupCommandBufferBeginInfo
p = do
    "heapIndex" ::: Word32
deviceMask <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupCommandBufferBeginInfo
p Ptr DeviceGroupCommandBufferBeginInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    DeviceGroupCommandBufferBeginInfo
-> IO DeviceGroupCommandBufferBeginInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupCommandBufferBeginInfo
 -> IO DeviceGroupCommandBufferBeginInfo)
-> DeviceGroupCommandBufferBeginInfo
-> IO DeviceGroupCommandBufferBeginInfo
forall a b. (a -> b) -> a -> b
$ ("heapIndex" ::: Word32) -> DeviceGroupCommandBufferBeginInfo
DeviceGroupCommandBufferBeginInfo
             "heapIndex" ::: Word32
deviceMask

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

instance Zero DeviceGroupCommandBufferBeginInfo where
  zero :: DeviceGroupCommandBufferBeginInfo
zero = ("heapIndex" ::: Word32) -> DeviceGroupCommandBufferBeginInfo
DeviceGroupCommandBufferBeginInfo
           "heapIndex" ::: Word32
forall a. Zero a => a
zero


-- | VkDeviceGroupSubmitInfo - Structure indicating which physical devices
-- execute semaphore operations and command buffers
--
-- = Description
--
-- If this structure is not present, semaphore operations and command
-- buffers execute on device index zero.
--
-- == Valid Usage
--
-- -   @waitSemaphoreCount@ /must/ equal
--     'Vulkan.Core10.Queue.SubmitInfo'::@waitSemaphoreCount@
--
-- -   @commandBufferCount@ /must/ equal
--     'Vulkan.Core10.Queue.SubmitInfo'::@commandBufferCount@
--
-- -   @signalSemaphoreCount@ /must/ equal
--     'Vulkan.Core10.Queue.SubmitInfo'::@signalSemaphoreCount@
--
-- -   All elements of @pWaitSemaphoreDeviceIndices@ and
--     @pSignalSemaphoreDeviceIndices@ /must/ be valid device indices
--
-- -   All elements of @pCommandBufferDeviceMasks@ /must/ be valid device
--     masks
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO'
--
-- -   If @waitSemaphoreCount@ is not @0@, @pWaitSemaphoreDeviceIndices@
--     /must/ be a valid pointer to an array of @waitSemaphoreCount@
--     @uint32_t@ values
--
-- -   If @commandBufferCount@ is not @0@, @pCommandBufferDeviceMasks@
--     /must/ be a valid pointer to an array of @commandBufferCount@
--     @uint32_t@ values
--
-- -   If @signalSemaphoreCount@ is not @0@,
--     @pSignalSemaphoreDeviceIndices@ /must/ be a valid pointer to an
--     array of @signalSemaphoreCount@ @uint32_t@ values
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceGroupSubmitInfo = DeviceGroupSubmitInfo
  { -- | @pWaitSemaphoreDeviceIndices@ is a pointer to an array of
    -- @waitSemaphoreCount@ device indices indicating which physical device
    -- executes the semaphore wait operation in the corresponding element of
    -- 'Vulkan.Core10.Queue.SubmitInfo'::@pWaitSemaphores@.
    DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32)
waitSemaphoreDeviceIndices :: Vector Word32
  , -- | @pCommandBufferDeviceMasks@ is a pointer to an array of
    -- @commandBufferCount@ device masks indicating which physical devices
    -- execute the command buffer in the corresponding element of
    -- 'Vulkan.Core10.Queue.SubmitInfo'::@pCommandBuffers@. A physical device
    -- executes the command buffer if the corresponding bit is set in the mask.
    DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32)
commandBufferDeviceMasks :: Vector Word32
  , -- | @pSignalSemaphoreDeviceIndices@ is a pointer to an array of
    -- @signalSemaphoreCount@ device indices indicating which physical device
    -- executes the semaphore signal operation in the corresponding element of
    -- 'Vulkan.Core10.Queue.SubmitInfo'::@pSignalSemaphores@.
    DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32)
signalSemaphoreDeviceIndices :: Vector Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupSubmitInfo)
#endif
deriving instance Show DeviceGroupSubmitInfo

instance ToCStruct DeviceGroupSubmitInfo where
  withCStruct :: DeviceGroupSubmitInfo
-> (Ptr DeviceGroupSubmitInfo -> IO b) -> IO b
withCStruct x :: DeviceGroupSubmitInfo
x f :: Ptr DeviceGroupSubmitInfo -> IO b
f = Int -> Int -> (Ptr DeviceGroupSubmitInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr DeviceGroupSubmitInfo -> IO b) -> IO b)
-> (Ptr DeviceGroupSubmitInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceGroupSubmitInfo
p -> Ptr DeviceGroupSubmitInfo -> DeviceGroupSubmitInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceGroupSubmitInfo
p DeviceGroupSubmitInfo
x (Ptr DeviceGroupSubmitInfo -> IO b
f Ptr DeviceGroupSubmitInfo
p)
  pokeCStruct :: Ptr DeviceGroupSubmitInfo -> DeviceGroupSubmitInfo -> IO b -> IO b
pokeCStruct p :: Ptr DeviceGroupSubmitInfo
p DeviceGroupSubmitInfo{..} 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 DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO)
    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 DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    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 ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> "heapIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ("heapIndex" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("heapIndex" ::: Word32) -> Int)
-> Vector ("heapIndex" ::: Word32) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ("heapIndex" ::: Word32)
waitSemaphoreDeviceIndices)) :: Word32))
    Ptr ("heapIndex" ::: Word32)
pPWaitSemaphoreDeviceIndices' <- ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("heapIndex" ::: Word32)))
-> ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector ("heapIndex" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("heapIndex" ::: Word32)
waitSemaphoreDeviceIndices)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> ("heapIndex" ::: Word32) -> IO ())
-> Vector ("heapIndex" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "heapIndex" ::: Word32
e -> Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("heapIndex" ::: Word32)
pPWaitSemaphoreDeviceIndices' Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("heapIndex" ::: Word32
e)) (Vector ("heapIndex" ::: Word32)
waitSemaphoreDeviceIndices)
    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 ("heapIndex" ::: Word32))
-> Ptr ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32)
pPWaitSemaphoreDeviceIndices')
    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 ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> "heapIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ("heapIndex" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("heapIndex" ::: Word32) -> Int)
-> Vector ("heapIndex" ::: Word32) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ("heapIndex" ::: Word32)
commandBufferDeviceMasks)) :: Word32))
    Ptr ("heapIndex" ::: Word32)
pPCommandBufferDeviceMasks' <- ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("heapIndex" ::: Word32)))
-> ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector ("heapIndex" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("heapIndex" ::: Word32)
commandBufferDeviceMasks)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> ("heapIndex" ::: Word32) -> IO ())
-> Vector ("heapIndex" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "heapIndex" ::: Word32
e -> Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("heapIndex" ::: Word32)
pPCommandBufferDeviceMasks' Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("heapIndex" ::: Word32
e)) (Vector ("heapIndex" ::: Word32)
commandBufferDeviceMasks)
    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 ("heapIndex" ::: Word32))
-> Ptr ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32)
pPCommandBufferDeviceMasks')
    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 ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> "heapIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ("heapIndex" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("heapIndex" ::: Word32) -> Int)
-> Vector ("heapIndex" ::: Word32) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ("heapIndex" ::: Word32)
signalSemaphoreDeviceIndices)) :: Word32))
    Ptr ("heapIndex" ::: Word32)
pPSignalSemaphoreDeviceIndices' <- ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("heapIndex" ::: Word32)))
-> ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector ("heapIndex" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("heapIndex" ::: Word32)
signalSemaphoreDeviceIndices)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> ("heapIndex" ::: Word32) -> IO ())
-> Vector ("heapIndex" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "heapIndex" ::: Word32
e -> Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("heapIndex" ::: Word32)
pPSignalSemaphoreDeviceIndices' Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("heapIndex" ::: Word32
e)) (Vector ("heapIndex" ::: Word32)
signalSemaphoreDeviceIndices)
    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 ("heapIndex" ::: Word32))
-> Ptr ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32)
pPSignalSemaphoreDeviceIndices')
    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 = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeviceGroupSubmitInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceGroupSubmitInfo
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 DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO)
    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 DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("heapIndex" ::: Word32)
pPWaitSemaphoreDeviceIndices' <- ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("heapIndex" ::: Word32)))
-> ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> ("heapIndex" ::: Word32) -> IO ())
-> Vector ("heapIndex" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "heapIndex" ::: Word32
e -> Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("heapIndex" ::: Word32)
pPWaitSemaphoreDeviceIndices' Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("heapIndex" ::: Word32
e)) (Vector ("heapIndex" ::: Word32)
forall a. Monoid a => a
mempty)
    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 ("heapIndex" ::: Word32))
-> Ptr ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32)
pPWaitSemaphoreDeviceIndices')
    Ptr ("heapIndex" ::: Word32)
pPCommandBufferDeviceMasks' <- ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("heapIndex" ::: Word32)))
-> ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> ("heapIndex" ::: Word32) -> IO ())
-> Vector ("heapIndex" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "heapIndex" ::: Word32
e -> Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("heapIndex" ::: Word32)
pPCommandBufferDeviceMasks' Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("heapIndex" ::: Word32
e)) (Vector ("heapIndex" ::: Word32)
forall a. Monoid a => a
mempty)
    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 ("heapIndex" ::: Word32))
-> Ptr ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32)
pPCommandBufferDeviceMasks')
    Ptr ("heapIndex" ::: Word32)
pPSignalSemaphoreDeviceIndices' <- ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("heapIndex" ::: Word32)))
-> ((Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("heapIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("heapIndex" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> ("heapIndex" ::: Word32) -> IO ())
-> Vector ("heapIndex" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "heapIndex" ::: Word32
e -> Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("heapIndex" ::: Word32)
pPSignalSemaphoreDeviceIndices' Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("heapIndex" ::: Word32
e)) (Vector ("heapIndex" ::: Word32)
forall a. Monoid a => a
mempty)
    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 ("heapIndex" ::: Word32))
-> Ptr ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32)
pPSignalSemaphoreDeviceIndices')
    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 FromCStruct DeviceGroupSubmitInfo where
  peekCStruct :: Ptr DeviceGroupSubmitInfo -> IO DeviceGroupSubmitInfo
peekCStruct p :: Ptr DeviceGroupSubmitInfo
p = do
    "heapIndex" ::: Word32
waitSemaphoreCount <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Ptr ("heapIndex" ::: Word32)
pWaitSemaphoreDeviceIndices <- Ptr (Ptr ("heapIndex" ::: Word32))
-> IO (Ptr ("heapIndex" ::: Word32))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32)))
    Vector ("heapIndex" ::: Word32)
pWaitSemaphoreDeviceIndices' <- Int
-> (Int -> IO ("heapIndex" ::: Word32))
-> IO (Vector ("heapIndex" ::: Word32))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("heapIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "heapIndex" ::: Word32
waitSemaphoreCount) (\i :: Int
i -> Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("heapIndex" ::: Word32)
pWaitSemaphoreDeviceIndices Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    "heapIndex" ::: Word32
commandBufferCount <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr ("heapIndex" ::: Word32)
pCommandBufferDeviceMasks <- Ptr (Ptr ("heapIndex" ::: Word32))
-> IO (Ptr ("heapIndex" ::: Word32))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Word32)))
    Vector ("heapIndex" ::: Word32)
pCommandBufferDeviceMasks' <- Int
-> (Int -> IO ("heapIndex" ::: Word32))
-> IO (Vector ("heapIndex" ::: Word32))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("heapIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "heapIndex" ::: Word32
commandBufferCount) (\i :: Int
i -> Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("heapIndex" ::: Word32)
pCommandBufferDeviceMasks Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    "heapIndex" ::: Word32
signalSemaphoreCount <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo -> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Ptr ("heapIndex" ::: Word32)
pSignalSemaphoreDeviceIndices <- Ptr (Ptr ("heapIndex" ::: Word32))
-> IO (Ptr ("heapIndex" ::: Word32))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr DeviceGroupSubmitInfo
p Ptr DeviceGroupSubmitInfo
-> Int -> Ptr (Ptr ("heapIndex" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr Word32)))
    Vector ("heapIndex" ::: Word32)
pSignalSemaphoreDeviceIndices' <- Int
-> (Int -> IO ("heapIndex" ::: Word32))
-> IO (Vector ("heapIndex" ::: Word32))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("heapIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "heapIndex" ::: Word32
signalSemaphoreCount) (\i :: Int
i -> Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("heapIndex" ::: Word32)
pSignalSemaphoreDeviceIndices Ptr ("heapIndex" ::: Word32) -> Int -> Ptr ("heapIndex" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    DeviceGroupSubmitInfo -> IO DeviceGroupSubmitInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupSubmitInfo -> IO DeviceGroupSubmitInfo)
-> DeviceGroupSubmitInfo -> IO DeviceGroupSubmitInfo
forall a b. (a -> b) -> a -> b
$ Vector ("heapIndex" ::: Word32)
-> Vector ("heapIndex" ::: Word32)
-> Vector ("heapIndex" ::: Word32)
-> DeviceGroupSubmitInfo
DeviceGroupSubmitInfo
             Vector ("heapIndex" ::: Word32)
pWaitSemaphoreDeviceIndices' Vector ("heapIndex" ::: Word32)
pCommandBufferDeviceMasks' Vector ("heapIndex" ::: Word32)
pSignalSemaphoreDeviceIndices'

instance Zero DeviceGroupSubmitInfo where
  zero :: DeviceGroupSubmitInfo
zero = Vector ("heapIndex" ::: Word32)
-> Vector ("heapIndex" ::: Word32)
-> Vector ("heapIndex" ::: Word32)
-> DeviceGroupSubmitInfo
DeviceGroupSubmitInfo
           Vector ("heapIndex" ::: Word32)
forall a. Monoid a => a
mempty
           Vector ("heapIndex" ::: Word32)
forall a. Monoid a => a
mempty
           Vector ("heapIndex" ::: Word32)
forall a. Monoid a => a
mempty


-- | VkDeviceGroupBindSparseInfo - Structure indicating which instances are
-- bound
--
-- = Description
--
-- These device indices apply to all buffer and image memory binds included
-- in the batch pointing to this structure. The semaphore waits and signals
-- for the batch are executed only by the physical device specified by the
-- @resourceDeviceIndex@.
--
-- If this structure is not present, @resourceDeviceIndex@ and
-- @memoryDeviceIndex@ are assumed to be zero.
--
-- == Valid Usage
--
-- -   @resourceDeviceIndex@ and @memoryDeviceIndex@ /must/ both be valid
--     device indices
--
-- -   Each memory allocation bound in this batch /must/ have allocated an
--     instance for @memoryDeviceIndex@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO'
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceGroupBindSparseInfo = DeviceGroupBindSparseInfo
  { -- | @resourceDeviceIndex@ is a device index indicating which instance of the
    -- resource is bound.
    DeviceGroupBindSparseInfo -> "heapIndex" ::: Word32
resourceDeviceIndex :: Word32
  , -- | @memoryDeviceIndex@ is a device index indicating which instance of the
    -- memory the resource instance is bound to.
    DeviceGroupBindSparseInfo -> "heapIndex" ::: Word32
memoryDeviceIndex :: Word32
  }
  deriving (Typeable, DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool
(DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool)
-> (DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool)
-> Eq DeviceGroupBindSparseInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool
$c/= :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool
== :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool
$c== :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupBindSparseInfo)
#endif
deriving instance Show DeviceGroupBindSparseInfo

instance ToCStruct DeviceGroupBindSparseInfo where
  withCStruct :: DeviceGroupBindSparseInfo
-> (Ptr DeviceGroupBindSparseInfo -> IO b) -> IO b
withCStruct x :: DeviceGroupBindSparseInfo
x f :: Ptr DeviceGroupBindSparseInfo -> IO b
f = Int -> Int -> (Ptr DeviceGroupBindSparseInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DeviceGroupBindSparseInfo -> IO b) -> IO b)
-> (Ptr DeviceGroupBindSparseInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceGroupBindSparseInfo
p -> Ptr DeviceGroupBindSparseInfo
-> DeviceGroupBindSparseInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceGroupBindSparseInfo
p DeviceGroupBindSparseInfo
x (Ptr DeviceGroupBindSparseInfo -> IO b
f Ptr DeviceGroupBindSparseInfo
p)
  pokeCStruct :: Ptr DeviceGroupBindSparseInfo
-> DeviceGroupBindSparseInfo -> IO b -> IO b
pokeCStruct p :: Ptr DeviceGroupBindSparseInfo
p DeviceGroupBindSparseInfo{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("heapIndex" ::: Word32
resourceDeviceIndex)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("heapIndex" ::: Word32
memoryDeviceIndex)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeviceGroupBindSparseInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceGroupBindSparseInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("heapIndex" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("heapIndex" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DeviceGroupBindSparseInfo where
  peekCStruct :: Ptr DeviceGroupBindSparseInfo -> IO DeviceGroupBindSparseInfo
peekCStruct p :: Ptr DeviceGroupBindSparseInfo
p = do
    "heapIndex" ::: Word32
resourceDeviceIndex <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "heapIndex" ::: Word32
memoryDeviceIndex <- Ptr ("heapIndex" ::: Word32) -> IO ("heapIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupBindSparseInfo
p Ptr DeviceGroupBindSparseInfo
-> Int -> Ptr ("heapIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    DeviceGroupBindSparseInfo -> IO DeviceGroupBindSparseInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupBindSparseInfo -> IO DeviceGroupBindSparseInfo)
-> DeviceGroupBindSparseInfo -> IO DeviceGroupBindSparseInfo
forall a b. (a -> b) -> a -> b
$ ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32) -> DeviceGroupBindSparseInfo
DeviceGroupBindSparseInfo
             "heapIndex" ::: Word32
resourceDeviceIndex "heapIndex" ::: Word32
memoryDeviceIndex

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

instance Zero DeviceGroupBindSparseInfo where
  zero :: DeviceGroupBindSparseInfo
zero = ("heapIndex" ::: Word32)
-> ("heapIndex" ::: Word32) -> DeviceGroupBindSparseInfo
DeviceGroupBindSparseInfo
           "heapIndex" ::: Word32
forall a. Zero a => a
zero
           "heapIndex" ::: Word32
forall a. Zero a => a
zero