{-# language CPP #-}
module Vulkan.Core10.CommandBufferBuilding  ( cmdBindPipeline
                                            , cmdSetViewport
                                            , cmdSetScissor
                                            , cmdSetLineWidth
                                            , cmdSetDepthBias
                                            , cmdSetBlendConstants
                                            , cmdSetDepthBounds
                                            , cmdSetStencilCompareMask
                                            , cmdSetStencilWriteMask
                                            , cmdSetStencilReference
                                            , cmdBindDescriptorSets
                                            , cmdBindIndexBuffer
                                            , cmdBindVertexBuffers
                                            , cmdDraw
                                            , cmdDrawIndexed
                                            , cmdDrawIndirect
                                            , cmdDrawIndexedIndirect
                                            , cmdDispatch
                                            , cmdDispatchIndirect
                                            , cmdCopyBuffer
                                            , cmdCopyImage
                                            , cmdBlitImage
                                            , cmdCopyBufferToImage
                                            , cmdCopyImageToBuffer
                                            , cmdUpdateBuffer
                                            , cmdFillBuffer
                                            , cmdClearColorImage
                                            , cmdClearDepthStencilImage
                                            , cmdClearAttachments
                                            , cmdResolveImage
                                            , cmdSetEvent
                                            , cmdResetEvent
                                            , cmdWaitEvents
                                            , cmdWaitEventsSafe
                                            , cmdPipelineBarrier
                                            , cmdBeginQuery
                                            , cmdUseQuery
                                            , cmdEndQuery
                                            , cmdResetQueryPool
                                            , cmdWriteTimestamp
                                            , cmdCopyQueryPoolResults
                                            , cmdPushConstants
                                            , cmdBeginRenderPass
                                            , cmdUseRenderPass
                                            , cmdNextSubpass
                                            , cmdEndRenderPass
                                            , cmdExecuteCommands
                                            , ClearRect(..)
                                            , ImageSubresourceLayers(..)
                                            , BufferCopy(..)
                                            , ImageCopy(..)
                                            , ImageBlit(..)
                                            , BufferImageCopy(..)
                                            , ImageResolve(..)
                                            , RenderPassBeginInfo(..)
                                            , ClearDepthStencilValue(..)
                                            , ClearAttachment(..)
                                            , ClearColorValue(..)
                                            , ClearValue(..)
                                            , IndexType(..)
                                            , SubpassContents(..)
                                            , StencilFaceFlagBits(..)
                                            , StencilFaceFlags
                                            ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.Trans.Cont (runContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Foreign.C.Types (CFloat(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
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 Data.Int (Int32)
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.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (Buffer(..))
import Vulkan.Core10.OtherTypes (BufferMemoryBarrier)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlagBits(..))
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags)
import Vulkan.Core10.Handles (DescriptorSet)
import Vulkan.Core10.Handles (DescriptorSet(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginQuery))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginRenderPass))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBindDescriptorSets))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBindIndexBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBindPipeline))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBindVertexBuffers))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBlitImage))
import Vulkan.Dynamic (DeviceCmds(pVkCmdClearAttachments))
import Vulkan.Dynamic (DeviceCmds(pVkCmdClearColorImage))
import Vulkan.Dynamic (DeviceCmds(pVkCmdClearDepthStencilImage))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyBufferToImage))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyImage))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyImageToBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyQueryPoolResults))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDispatch))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDispatchIndirect))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDraw))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawIndexed))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawIndexedIndirect))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawIndirect))
import Vulkan.Dynamic (DeviceCmds(pVkCmdEndQuery))
import Vulkan.Dynamic (DeviceCmds(pVkCmdEndRenderPass))
import Vulkan.Dynamic (DeviceCmds(pVkCmdExecuteCommands))
import Vulkan.Dynamic (DeviceCmds(pVkCmdFillBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkCmdNextSubpass))
import Vulkan.Dynamic (DeviceCmds(pVkCmdPipelineBarrier))
import Vulkan.Dynamic (DeviceCmds(pVkCmdPushConstants))
import Vulkan.Dynamic (DeviceCmds(pVkCmdResetEvent))
import Vulkan.Dynamic (DeviceCmds(pVkCmdResetQueryPool))
import Vulkan.Dynamic (DeviceCmds(pVkCmdResolveImage))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetBlendConstants))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthBias))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthBounds))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetEvent))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLineWidth))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetScissor))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilCompareMask))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilReference))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilWriteMask))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewport))
import Vulkan.Dynamic (DeviceCmds(pVkCmdUpdateBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkCmdWaitEvents))
import Vulkan.Dynamic (DeviceCmds(pVkCmdWriteTimestamp))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (DeviceGroupRenderPassBeginInfo)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Event)
import Vulkan.Core10.Handles (Event(..))
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.FundamentalTypes (Extent3D)
import Vulkan.Core10.Enums.Filter (Filter)
import Vulkan.Core10.Enums.Filter (Filter(..))
import Vulkan.Core10.Handles (Framebuffer)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout(..))
import Vulkan.Core10.OtherTypes (ImageMemoryBarrier)
import Vulkan.Core10.ImageView (ImageSubresourceRange)
import Vulkan.Core10.Enums.IndexType (IndexType)
import Vulkan.Core10.Enums.IndexType (IndexType(..))
import Vulkan.Core10.OtherTypes (MemoryBarrier)
import Vulkan.Core10.FundamentalTypes (Offset3D)
import Vulkan.Core10.Handles (Pipeline)
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..))
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlagBits)
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlagBits(..))
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlagBits(..))
import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlags)
import Vulkan.Core10.Handles (QueryPool)
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlagBits(..))
import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlags)
import Vulkan.Core10.FundamentalTypes (Rect2D)
import Vulkan.Core10.Handles (RenderPass)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer (RenderPassAttachmentBeginInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_sample_locations (RenderPassSampleLocationsBeginInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_QCOM_render_pass_transform (RenderPassTransformBeginInfoQCOM)
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlagBits(..))
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlagBits(..))
import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.SubpassContents (SubpassContents)
import Vulkan.Core10.Enums.SubpassContents (SubpassContents(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Core10.Pipeline (Viewport)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO))
import Vulkan.Core10.Enums.IndexType (IndexType(..))
import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlagBits(..))
import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlags)
import Vulkan.Core10.Enums.SubpassContents (SubpassContents(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBindPipeline
  :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()

-- | vkCmdBindPipeline - Bind a pipeline object to a command buffer
--
-- = Description
--
-- Once bound, a pipeline binding affects subsequent commands that interact
-- with the given pipeline type in the command buffer until a different
-- pipeline of the same type is bound to the bind point. Commands that do
-- not interact with the given pipeline type /must/ not be affected by the
-- pipeline state.
--
-- -   The pipeline bound to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE'
--     controls the behavior of all
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#dispatch dispatching commands>.
--
-- -   The pipeline bound to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--     controls the behavior of all
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing drawing commands>.
--
-- -   The pipeline bound to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR'
--     controls the behavior of
--     'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysKHR' and
--     'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysIndirectKHR'.
--
-- == Valid Usage
--
-- -   If @pipelineBindPoint@ is
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE',
--     the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   If @pipelineBindPoint@ is
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS',
--     the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   If @pipelineBindPoint@ is
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE',
--     @pipeline@ /must/ be a compute pipeline
--
-- -   If @pipelineBindPoint@ is
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS',
--     @pipeline@ /must/ be a graphics pipeline
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-variableMultisampleRate variable multisample rate>
--     feature is not supported, @pipeline@ is a graphics pipeline, the
--     current subpass
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments uses no attachments>,
--     and this is not the first call to this function with a graphics
--     pipeline after transitioning to the current subpass, then the sample
--     count specified by this pipeline /must/ match that set in the
--     previous pipeline
--
-- -   If
--     'Vulkan.Extensions.VK_EXT_sample_locations.PhysicalDeviceSampleLocationsPropertiesEXT'::@variableSampleLocations@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', and @pipeline@ is a
--     graphics pipeline created with a
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--     structure having its @sampleLocationsEnable@ member set to
--     'Vulkan.Core10.FundamentalTypes.TRUE' but without
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT'
--     enabled then the current render pass instance /must/ have been begun
--     by specifying a
--     'Vulkan.Extensions.VK_EXT_sample_locations.RenderPassSampleLocationsBeginInfoEXT'
--     structure whose @pPostSubpassSampleLocations@ member contains an
--     element with a @subpassIndex@ matching the current subpass index and
--     the @sampleLocationsInfo@ member of that element /must/ match the
--     @sampleLocationsInfo@ specified in
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--     when the pipeline was created
--
-- -   This command /must/ not be recorded when transform feedback is
--     active
--
-- -   If @pipelineBindPoint@ is
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR',
--     the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   If @pipelineBindPoint@ is
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR',
--     the @pipeline@ /must/ be a ray tracing pipeline
--
-- -   The @pipeline@ /must/ not have been created with
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR'
--     set
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pipelineBindPoint@ /must/ be a valid
--     'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value
--
-- -   @pipeline@ /must/ be a valid 'Vulkan.Core10.Handles.Pipeline' 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, or compute operations
--
-- -   Both of @commandBuffer@, and @pipeline@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Pipeline',
-- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint'
cmdBindPipeline :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer that the pipeline will be bound
                   -- to.
                   CommandBuffer
                -> -- | @pipelineBindPoint@ is a
                   -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value
                   -- specifying to which bind point the pipeline is bound. Binding one does
                   -- not disturb the others.
                   PipelineBindPoint
                -> -- | @pipeline@ is the pipeline to be bound.
                   Pipeline
                -> io ()
cmdBindPipeline :: CommandBuffer -> PipelineBindPoint -> Pipeline -> io ()
cmdBindPipeline commandBuffer :: CommandBuffer
commandBuffer pipelineBindPoint :: PipelineBindPoint
pipelineBindPoint pipeline :: Pipeline
pipeline = 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 vkCmdBindPipelinePtr :: FunPtr
  (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
vkCmdBindPipelinePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
pVkCmdBindPipeline (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
vkCmdBindPipelinePtr FunPtr
  (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCmdBindPipeline is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBindPipeline' :: Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
vkCmdBindPipeline' = FunPtr
  (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
-> Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
mkVkCmdBindPipeline FunPtr
  (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ())
vkCmdBindPipelinePtr
  Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()
vkCmdBindPipeline' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (PipelineBindPoint
pipelineBindPoint) (Pipeline
pipeline)
  () -> 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" mkVkCmdSetViewport
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Viewport -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Viewport -> IO ()

-- | vkCmdSetViewport - Set the viewport on a command buffer
--
-- = Description
--
-- The viewport parameters taken from element i of @pViewports@ replace the
-- current state for the viewport index @firstViewport@ + i, for i in [0,
-- @viewportCount@).
--
-- == Valid Usage
--
-- -   @firstViewport@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@
--
-- -   The sum of @firstViewport@ and @viewportCount@ /must/ be between @1@
--     and
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@,
--     inclusive
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @firstViewport@ /must/ be @0@
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @viewportCount@ /must/ be @1@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pViewports@ /must/ be a valid pointer to an array of
--     @viewportCount@ valid 'Vulkan.Core10.Pipeline.Viewport' structures
--
-- -   @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 operations
--
-- -   @viewportCount@ /must/ be greater than @0@
--
-- == 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Pipeline.Viewport'
cmdSetViewport :: forall io
                . (MonadIO io)
               => -- | @commandBuffer@ is the command buffer into which the command will be
                  -- recorded.
                  CommandBuffer
               -> -- | @firstViewport@ is the index of the first viewport whose parameters are
                  -- updated by the command.
                  ("firstViewport" ::: Word32)
               -> -- | @pViewports@ is a pointer to an array of
                  -- 'Vulkan.Core10.Pipeline.Viewport' structures specifying viewport
                  -- parameters.
                  ("viewports" ::: Vector Viewport)
               -> io ()
cmdSetViewport :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("viewports" ::: Vector Viewport)
-> io ()
cmdSetViewport commandBuffer :: CommandBuffer
commandBuffer firstViewport :: "firstViewport" ::: Word32
firstViewport viewports :: "viewports" ::: Vector Viewport
viewports = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetViewportPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewports" ::: Ptr Viewport)
   -> IO ())
vkCmdSetViewportPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pViewports" ::: Ptr Viewport)
      -> IO ())
pVkCmdSetViewport (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewports" ::: Ptr Viewport)
   -> IO ())
vkCmdSetViewportPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewports" ::: Ptr Viewport)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pViewports" ::: Ptr Viewport)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewports" ::: Ptr Viewport)
   -> 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 vkCmdSetViewport is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetViewport' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pViewports" ::: Ptr Viewport)
-> IO ()
vkCmdSetViewport' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewports" ::: Ptr Viewport)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pViewports" ::: Ptr Viewport)
-> IO ()
mkVkCmdSetViewport FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewports" ::: Ptr Viewport)
   -> IO ())
vkCmdSetViewportPtr
  "pViewports" ::: Ptr Viewport
pPViewports <- ((("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ())
-> ContT () IO ("pViewports" ::: Ptr Viewport)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ())
 -> ContT () IO ("pViewports" ::: Ptr Viewport))
-> ((("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ())
-> ContT () IO ("pViewports" ::: Ptr Viewport)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Viewport ((("viewports" ::: Vector Viewport) -> Int
forall a. Vector a -> Int
Data.Vector.length ("viewports" ::: Vector Viewport
viewports)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 4
  (Int -> Viewport -> ContT () IO ())
-> ("viewports" ::: Vector Viewport) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Viewport
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pViewports" ::: Ptr Viewport) -> Viewport -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pViewports" ::: Ptr Viewport
pPViewports ("pViewports" ::: Ptr Viewport)
-> Int -> "pViewports" ::: Ptr Viewport
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Viewport) (Viewport
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("viewports" ::: Vector Viewport
viewports)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pViewports" ::: Ptr Viewport)
-> IO ()
vkCmdSetViewport' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstViewport" ::: Word32
firstViewport) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("viewports" ::: Vector Viewport) -> Int
forall a. Vector a -> Int
Data.Vector.length (("viewports" ::: Vector Viewport) -> Int)
-> ("viewports" ::: Vector Viewport) -> Int
forall a b. (a -> b) -> a -> b
$ ("viewports" ::: Vector Viewport
viewports)) :: Word32)) ("pViewports" ::: Ptr Viewport
pPViewports)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdSetScissor - Set the dynamic scissor rectangles on a command buffer
--
-- = Description
--
-- The scissor rectangles taken from element i of @pScissors@ replace the
-- current state for the scissor index @firstScissor@ + i, for i in [0,
-- @scissorCount@).
--
-- This command sets the state for a given draw when the graphics pipeline
-- is created with 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
--
-- == Valid Usage
--
-- -   @firstScissor@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@
--
-- -   The sum of @firstScissor@ and @scissorCount@ /must/ be between @1@
--     and
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@,
--     inclusive
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @firstScissor@ /must/ be @0@
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @scissorCount@ /must/ be @1@
--
-- -   The @x@ and @y@ members of @offset@ member of any element of
--     @pScissors@ /must/ be greater than or equal to @0@
--
-- -   Evaluation of (@offset.x@ + @extent.width@) /must/ not cause a
--     signed integer addition overflow for any element of @pScissors@
--
-- -   Evaluation of (@offset.y@ + @extent.height@) /must/ not cause a
--     signed integer addition overflow for any element of @pScissors@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pScissors@ /must/ be a valid pointer to an array of @scissorCount@
--     'Vulkan.Core10.FundamentalTypes.Rect2D' structures
--
-- -   @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 operations
--
-- -   @scissorCount@ /must/ be greater than @0@
--
-- == 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D'
cmdSetScissor :: forall io
               . (MonadIO io)
              => -- | @commandBuffer@ is the command buffer into which the command will be
                 -- recorded.
                 CommandBuffer
              -> -- | @firstScissor@ is the index of the first scissor whose state is updated
                 -- by the command.
                 ("firstScissor" ::: Word32)
              -> -- | @pScissors@ is a pointer to an array of
                 -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining scissor
                 -- rectangles.
                 ("scissors" ::: Vector Rect2D)
              -> io ()
cmdSetScissor :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("scissors" ::: Vector Rect2D)
-> io ()
cmdSetScissor commandBuffer :: CommandBuffer
commandBuffer firstScissor :: "firstViewport" ::: Word32
firstScissor scissors :: "scissors" ::: Vector Rect2D
scissors = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetScissorPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pScissors" ::: Ptr Rect2D)
   -> IO ())
vkCmdSetScissorPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pScissors" ::: Ptr Rect2D)
      -> IO ())
pVkCmdSetScissor (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pScissors" ::: Ptr Rect2D)
   -> IO ())
vkCmdSetScissorPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pScissors" ::: Ptr Rect2D)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pScissors" ::: Ptr Rect2D)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pScissors" ::: Ptr Rect2D)
   -> 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 vkCmdSetScissor is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetScissor' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pScissors" ::: Ptr Rect2D)
-> IO ()
vkCmdSetScissor' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pScissors" ::: Ptr Rect2D)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pScissors" ::: Ptr Rect2D)
-> IO ()
mkVkCmdSetScissor FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pScissors" ::: Ptr Rect2D)
   -> IO ())
vkCmdSetScissorPtr
  "pScissors" ::: Ptr Rect2D
pPScissors <- ((("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ())
-> ContT () IO ("pScissors" ::: Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ())
 -> ContT () IO ("pScissors" ::: Ptr Rect2D))
-> ((("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ())
-> ContT () IO ("pScissors" ::: Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D ((("scissors" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length ("scissors" ::: Vector Rect2D
scissors)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
  (Int -> Rect2D -> ContT () IO ())
-> ("scissors" ::: Vector Rect2D) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pScissors" ::: Ptr Rect2D) -> Rect2D -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pScissors" ::: Ptr Rect2D
pPScissors ("pScissors" ::: Ptr Rect2D) -> Int -> "pScissors" ::: 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 () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("scissors" ::: Vector Rect2D
scissors)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pScissors" ::: Ptr Rect2D)
-> IO ()
vkCmdSetScissor' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstViewport" ::: Word32
firstScissor) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("scissors" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length (("scissors" ::: Vector Rect2D) -> Int)
-> ("scissors" ::: Vector Rect2D) -> Int
forall a b. (a -> b) -> a -> b
$ ("scissors" ::: Vector Rect2D
scissors)) :: Word32)) ("pScissors" ::: Ptr Rect2D
pPScissors)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdSetLineWidth - Set the dynamic line width state
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-wideLines wide lines>
--     feature is not enabled, @lineWidth@ /must/ be @1.0@
--
-- == 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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetLineWidth :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command will be
                   -- recorded.
                   CommandBuffer
                -> -- | @lineWidth@ is the width of rasterized line segments.
                   ("lineWidth" ::: Float)
                -> io ()
cmdSetLineWidth :: CommandBuffer -> ("lineWidth" ::: Float) -> io ()
cmdSetLineWidth commandBuffer :: CommandBuffer
commandBuffer lineWidth :: "lineWidth" ::: Float
lineWidth = 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 vkCmdSetLineWidthPtr :: FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
vkCmdSetLineWidthPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
pVkCmdSetLineWidth (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
vkCmdSetLineWidthPtr FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> 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 vkCmdSetLineWidth is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetLineWidth' :: Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()
vkCmdSetLineWidth' = FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
-> Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()
mkVkCmdSetLineWidth FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ())
vkCmdSetLineWidthPtr
  Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()
vkCmdSetLineWidth' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
lineWidth))
  () -> 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" mkVkCmdSetDepthBias
  :: FunPtr (Ptr CommandBuffer_T -> CFloat -> CFloat -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> CFloat -> CFloat -> IO ()

-- | vkCmdSetDepthBias - Set the depth bias dynamic state
--
-- = Description
--
-- If @depthBiasEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE', no depth
-- bias is applied and the fragment’s depth values are unchanged.
--
-- @depthBiasSlopeFactor@ scales the maximum depth slope of the polygon,
-- and @depthBiasConstantFactor@ scales an implementation-dependent
-- constant that relates to the usable resolution of the depth buffer. The
-- resulting values are summed to produce the depth bias value which is
-- then clamped to a minimum or maximum value specified by
-- @depthBiasClamp@. @depthBiasSlopeFactor@, @depthBiasConstantFactor@, and
-- @depthBiasClamp@ /can/ each be positive, negative, or zero.
--
-- The maximum depth slope m of a triangle is
--
-- \[m = \sqrt{ \left({{\partial z_f} \over {\partial x_f}}\right)^2
--         +  \left({{\partial z_f} \over {\partial y_f}}\right)^2}\]
--
-- where (xf, yf, zf) is a point on the triangle. m /may/ be approximated
-- as
--
-- \[m = \max\left( \left| { {\partial z_f} \over {\partial x_f} } \right|,
--                \left| { {\partial z_f} \over {\partial y_f} } \right|
--        \right).\]
--
-- The minimum resolvable difference r is an implementation-dependent
-- parameter that depends on the depth buffer representation. It is the
-- smallest difference in framebuffer coordinate z values that is
-- guaranteed to remain distinct throughout polygon rasterization and in
-- the depth buffer. All pairs of fragments generated by the rasterization
-- of two polygons with otherwise identical vertices, but @z@f values that
-- differ by r, will have distinct depth values.
--
-- For fixed-point depth buffer representations, r is constant throughout
-- the range of the entire depth buffer. For floating-point depth buffers,
-- there is no single minimum resolvable difference. In this case, the
-- minimum resolvable difference for a given polygon is dependent on the
-- maximum exponent, e, in the range of z values spanned by the primitive.
-- If n is the number of bits in the floating-point mantissa, the minimum
-- resolvable difference, r, for the given primitive is defined as
--
-- -   r = 2e-n
--
-- If a triangle is rasterized using the
-- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL_RECTANGLE_NV' polygon
-- mode, then this minimum resolvable difference /may/ not be resolvable
-- for samples outside of the triangle, where the depth is extrapolated.
--
-- If no depth buffer is present, r is undefined.
--
-- The bias value o for a polygon is
--
-- \[\begin{aligned}
-- o &= \mathrm{dbclamp}( m \times \mathtt{depthBiasSlopeFactor} + r \times \mathtt{depthBiasConstantFactor} ) \\
-- \text{where} &\quad \mathrm{dbclamp}(x) =
-- \begin{cases}
--     x                                 & \mathtt{depthBiasClamp} = 0 \ \text{or}\ \texttt{NaN} \\
--     \min(x, \mathtt{depthBiasClamp})  & \mathtt{depthBiasClamp} > 0 \\
--     \max(x, \mathtt{depthBiasClamp})  & \mathtt{depthBiasClamp} < 0 \\
-- \end{cases}
-- \end{aligned}\]
--
-- m is computed as described above. If the depth buffer uses a fixed-point
-- representation, m is a function of depth values in the range [0,1], and
-- o is applied to depth values in the same range.
--
-- For fixed-point depth buffers, fragment depth values are always limited
-- to the range [0,1] by clamping after depth bias addition is performed.
-- Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled,
-- fragment depth values are clamped even when the depth buffer uses a
-- floating-point representation.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBiasClamp depth bias clamping>
--     feature is not enabled, @depthBiasClamp@ /must/ be @0.0@
--
-- == 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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDepthBias :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command will be
                   -- recorded.
                   CommandBuffer
                -> -- | @depthBiasConstantFactor@ is a scalar factor controlling the constant
                   -- depth value added to each fragment.
                   ("depthBiasConstantFactor" ::: Float)
                -> -- | @depthBiasClamp@ is the maximum (or minimum) depth bias of a fragment.
                   ("depthBiasClamp" ::: Float)
                -> -- | @depthBiasSlopeFactor@ is a scalar factor applied to a fragment’s slope
                   -- in depth bias calculations.
                   ("depthBiasSlopeFactor" ::: Float)
                -> io ()
cmdSetDepthBias :: CommandBuffer
-> ("lineWidth" ::: Float)
-> ("lineWidth" ::: Float)
-> ("lineWidth" ::: Float)
-> io ()
cmdSetDepthBias commandBuffer :: CommandBuffer
commandBuffer depthBiasConstantFactor :: "lineWidth" ::: Float
depthBiasConstantFactor depthBiasClamp :: "lineWidth" ::: Float
depthBiasClamp depthBiasSlopeFactor :: "lineWidth" ::: Float
depthBiasSlopeFactor = 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 vkCmdSetDepthBiasPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> IO ())
vkCmdSetDepthBiasPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("lineWidth" ::: CFloat)
      -> ("lineWidth" ::: CFloat)
      -> ("lineWidth" ::: CFloat)
      -> IO ())
pVkCmdSetDepthBias (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> IO ())
vkCmdSetDepthBiasPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("lineWidth" ::: CFloat)
      -> ("lineWidth" ::: CFloat)
      -> ("lineWidth" ::: CFloat)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> 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 vkCmdSetDepthBias is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetDepthBias' :: Ptr CommandBuffer_T
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> IO ()
vkCmdSetDepthBias' = FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> IO ()
mkVkCmdSetDepthBias FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> ("lineWidth" ::: CFloat)
   -> IO ())
vkCmdSetDepthBiasPtr
  Ptr CommandBuffer_T
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> IO ()
vkCmdSetDepthBias' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
depthBiasConstantFactor)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
depthBiasClamp)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
depthBiasSlopeFactor))
  () -> 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" mkVkCmdSetBlendConstants
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (FixedArray 4 CFloat) -> IO ()) -> Ptr CommandBuffer_T -> Ptr (FixedArray 4 CFloat) -> IO ()

-- | vkCmdSetBlendConstants - Set the values of blend constants
--
-- == 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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetBlendConstants :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command will be
                        -- recorded.
                        CommandBuffer
                     -> -- | @blendConstants@ is a pointer to an array of four values specifying the
                        -- R, G, B, and A components of the blend constant color used in blending,
                        -- depending on the
                        -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blendfactors blend factor>.
                        ("blendConstants" ::: (Float, Float, Float, Float))
                     -> io ()
cmdSetBlendConstants :: CommandBuffer
-> ("blendConstants"
    ::: ("lineWidth" ::: Float, "lineWidth" ::: Float,
         "lineWidth" ::: Float, "lineWidth" ::: Float))
-> io ()
cmdSetBlendConstants commandBuffer :: CommandBuffer
commandBuffer blendConstants :: "blendConstants"
::: ("lineWidth" ::: Float, "lineWidth" ::: Float,
     "lineWidth" ::: Float, "lineWidth" ::: Float)
blendConstants = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetBlendConstantsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("blendConstants"
       ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> IO ())
vkCmdSetBlendConstantsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("blendConstants"
          ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
      -> IO ())
pVkCmdSetBlendConstants (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("blendConstants"
       ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> IO ())
vkCmdSetBlendConstantsPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("blendConstants"
       ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("blendConstants"
          ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("blendConstants"
       ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> 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 vkCmdSetBlendConstants is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetBlendConstants' :: Ptr CommandBuffer_T
-> ("blendConstants"
    ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
-> IO ()
vkCmdSetBlendConstants' = FunPtr
  (Ptr CommandBuffer_T
   -> ("blendConstants"
       ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("blendConstants"
    ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
-> IO ()
mkVkCmdSetBlendConstants FunPtr
  (Ptr CommandBuffer_T
   -> ("blendConstants"
       ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> IO ())
vkCmdSetBlendConstantsPtr
  "blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))
pBlendConstants <- ((("blendConstants"
   ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("blendConstants"
    ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))))
-> ((("blendConstants"
      ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("blendConstants"
     ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
    -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(FixedArray 4 CFloat) 16 4
  let pBlendConstants' :: Ptr ("lineWidth" ::: CFloat)
pBlendConstants' = ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
-> Ptr ("lineWidth" ::: CFloat)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr "blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))
pBlendConstants
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ case ("blendConstants"
::: ("lineWidth" ::: Float, "lineWidth" ::: Float,
     "lineWidth" ::: Float, "lineWidth" ::: Float)
blendConstants) of
    (e0 :: "lineWidth" ::: Float
e0, e1 :: "lineWidth" ::: Float
e1, e2 :: "lineWidth" ::: Float
e2, e3 :: "lineWidth" ::: Float
e3) -> do
      Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pBlendConstants' :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e0))
      Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pBlendConstants' Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e1))
      Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pBlendConstants' Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e2))
      Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pBlendConstants' Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e3))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("blendConstants"
    ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
-> IO ()
vkCmdSetBlendConstants' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))
pBlendConstants)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdSetDepthBounds - Set the depth bounds test values for a command
-- buffer
--
-- = Description
--
-- This command sets the state for a given draw when the graphics pipeline
-- is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
--
-- == Valid Usage
--
-- -   Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled
--     @minDepthBounds@ /must/ be between @0.0@ and @1.0@, inclusive
--
-- -   Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled
--     @maxDepthBounds@ /must/ be between @0.0@ and @1.0@, inclusive
--
-- == 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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDepthBounds :: forall io
                   . (MonadIO io)
                  => -- | @commandBuffer@ is the command buffer into which the command will be
                     -- recorded.
                     CommandBuffer
                  -> -- | @minDepthBounds@ is the minimum depth bound.
                     ("minDepthBounds" ::: Float)
                  -> -- | @maxDepthBounds@ is the maximum depth bound.
                     ("maxDepthBounds" ::: Float)
                  -> io ()
cmdSetDepthBounds :: CommandBuffer
-> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> io ()
cmdSetDepthBounds commandBuffer :: CommandBuffer
commandBuffer minDepthBounds :: "lineWidth" ::: Float
minDepthBounds maxDepthBounds :: "lineWidth" ::: Float
maxDepthBounds = 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 vkCmdSetDepthBoundsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
vkCmdSetDepthBoundsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
pVkCmdSetDepthBounds (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
vkCmdSetDepthBoundsPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> 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 vkCmdSetDepthBounds is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetDepthBounds' :: Ptr CommandBuffer_T
-> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
vkCmdSetDepthBounds' = FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
-> Ptr CommandBuffer_T
-> ("lineWidth" ::: CFloat)
-> ("lineWidth" ::: CFloat)
-> IO ()
mkVkCmdSetDepthBounds FunPtr
  (Ptr CommandBuffer_T
   -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ())
vkCmdSetDepthBoundsPtr
  Ptr CommandBuffer_T
-> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
vkCmdSetDepthBounds' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
minDepthBounds)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
maxDepthBounds))
  () -> 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" mkVkCmdSetStencilCompareMask
  :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()

-- | vkCmdSetStencilCompareMask - Set the stencil compare mask dynamic state
--
-- = Description
--
-- This command sets the state for a given draw when the graphics pipeline
-- is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @faceMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values
--
-- -   @faceMask@ /must/ not be @0@
--
-- -   @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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags'
cmdSetStencilCompareMask :: forall io
                          . (MonadIO io)
                         => -- | @commandBuffer@ is the command buffer into which the command will be
                            -- recorded.
                            CommandBuffer
                         -> -- | @faceMask@ is a bitmask of
                            -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' specifying
                            -- the set of stencil state for which to update the compare mask.
                            ("faceMask" ::: StencilFaceFlags)
                         -> -- | @compareMask@ is the new value to use as the stencil compare mask.
                            ("compareMask" ::: Word32)
                         -> io ()
cmdSetStencilCompareMask :: CommandBuffer
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> io ()
cmdSetStencilCompareMask commandBuffer :: CommandBuffer
commandBuffer faceMask :: "faceMask" ::: StencilFaceFlags
faceMask compareMask :: "firstViewport" ::: Word32
compareMask = 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 vkCmdSetStencilCompareMaskPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilCompareMaskPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("faceMask" ::: StencilFaceFlags)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdSetStencilCompareMask (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilCompareMaskPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("faceMask" ::: StencilFaceFlags)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: 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 vkCmdSetStencilCompareMask is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetStencilCompareMask' :: Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdSetStencilCompareMask' = FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdSetStencilCompareMask FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilCompareMaskPtr
  Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdSetStencilCompareMask' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("faceMask" ::: StencilFaceFlags
faceMask) ("firstViewport" ::: Word32
compareMask)
  () -> 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" mkVkCmdSetStencilWriteMask
  :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()

-- | vkCmdSetStencilWriteMask - Set the stencil write mask dynamic state
--
-- = Description
--
-- This command sets the state for a given draw when the graphics pipeline
-- is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' set
-- in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @faceMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values
--
-- -   @faceMask@ /must/ not be @0@
--
-- -   @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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags'
cmdSetStencilWriteMask :: forall io
                        . (MonadIO io)
                       => -- | @commandBuffer@ is the command buffer into which the command will be
                          -- recorded.
                          CommandBuffer
                       -> -- | @faceMask@ is a bitmask of
                          -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' specifying
                          -- the set of stencil state for which to update the write mask, as
                          -- described above for 'cmdSetStencilCompareMask'.
                          ("faceMask" ::: StencilFaceFlags)
                       -> -- | @writeMask@ is the new value to use as the stencil write mask.
                          ("writeMask" ::: Word32)
                       -> io ()
cmdSetStencilWriteMask :: CommandBuffer
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> io ()
cmdSetStencilWriteMask commandBuffer :: CommandBuffer
commandBuffer faceMask :: "faceMask" ::: StencilFaceFlags
faceMask writeMask :: "firstViewport" ::: Word32
writeMask = 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 vkCmdSetStencilWriteMaskPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilWriteMaskPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("faceMask" ::: StencilFaceFlags)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdSetStencilWriteMask (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilWriteMaskPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("faceMask" ::: StencilFaceFlags)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: 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 vkCmdSetStencilWriteMask is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetStencilWriteMask' :: Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdSetStencilWriteMask' = FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdSetStencilWriteMask FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilWriteMaskPtr
  Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdSetStencilWriteMask' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("faceMask" ::: StencilFaceFlags
faceMask) ("firstViewport" ::: Word32
writeMask)
  () -> 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" mkVkCmdSetStencilReference
  :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()

-- | vkCmdSetStencilReference - Set the stencil reference dynamic state
--
-- = Description
--
-- This command sets the state for a given draw when the graphics pipeline
-- is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' set
-- in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @faceMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values
--
-- -   @faceMask@ /must/ not be @0@
--
-- -   @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 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags'
cmdSetStencilReference :: forall io
                        . (MonadIO io)
                       => -- | @commandBuffer@ is the command buffer into which the command will be
                          -- recorded.
                          CommandBuffer
                       -> -- | @faceMask@ is a bitmask of
                          -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' specifying
                          -- the set of stencil state for which to update the reference value, as
                          -- described above for 'cmdSetStencilCompareMask'.
                          ("faceMask" ::: StencilFaceFlags)
                       -> -- | @reference@ is the new value to use as the stencil reference value.
                          ("reference" ::: Word32)
                       -> io ()
cmdSetStencilReference :: CommandBuffer
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> io ()
cmdSetStencilReference commandBuffer :: CommandBuffer
commandBuffer faceMask :: "faceMask" ::: StencilFaceFlags
faceMask reference :: "firstViewport" ::: Word32
reference = 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 vkCmdSetStencilReferencePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilReferencePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("faceMask" ::: StencilFaceFlags)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdSetStencilReference (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilReferencePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("faceMask" ::: StencilFaceFlags)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: 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 vkCmdSetStencilReference is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetStencilReference' :: Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdSetStencilReference' = FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdSetStencilReference FunPtr
  (Ptr CommandBuffer_T
   -> ("faceMask" ::: StencilFaceFlags)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdSetStencilReferencePtr
  Ptr CommandBuffer_T
-> ("faceMask" ::: StencilFaceFlags)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdSetStencilReference' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("faceMask" ::: StencilFaceFlags
faceMask) ("firstViewport" ::: Word32
reference)
  () -> 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" mkVkCmdBindDescriptorSets
  :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr DescriptorSet -> Word32 -> Ptr Word32 -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr DescriptorSet -> Word32 -> Ptr Word32 -> IO ()

-- | vkCmdBindDescriptorSets - Binds descriptor sets to a command buffer
--
-- = Description
--
-- 'cmdBindDescriptorSets' causes the sets numbered [@firstSet@..
-- @firstSet@+@descriptorSetCount@-1] to use the bindings stored in
-- @pDescriptorSets@[0..descriptorSetCount-1] for subsequent
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipeline-bindpoint-commands bound pipeline commands>
-- set by @pipelineBindPoint@. Any bindings that were previously applied
-- via these sets are no longer valid.
--
-- Once bound, a descriptor set affects rendering of subsequent commands
-- that interact with the given pipeline type in the command buffer until
-- either a different set is bound to the same set number, or the set is
-- disturbed as described in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility>.
--
-- A compatible descriptor set /must/ be bound for all set numbers that any
-- shaders in a pipeline access, at the time that a draw or dispatch
-- command is recorded to execute using that pipeline. However, if none of
-- the shaders in a pipeline statically use any bindings with a particular
-- set number, then no descriptor set need be bound for that set number,
-- even if the pipeline layout includes a non-trivial descriptor set layout
-- for that set number.
--
-- If any of the sets being bound include dynamic uniform or storage
-- buffers, then @pDynamicOffsets@ includes one element for each array
-- element in each dynamic descriptor type binding in each set. Values are
-- taken from @pDynamicOffsets@ in an order such that all entries for set N
-- come before set N+1; within a set, entries are ordered by the binding
-- numbers in the descriptor set layouts; and within a binding array,
-- elements are in order. @dynamicOffsetCount@ /must/ equal the total
-- number of dynamic descriptors in the sets being bound.
--
-- The effective offset used for dynamic uniform and storage buffer
-- bindings is the sum of the relative offset taken from @pDynamicOffsets@,
-- and the base address of the buffer plus base offset in the descriptor
-- set. The range of the dynamic uniform and storage buffer bindings is the
-- buffer range as specified in the descriptor set.
--
-- Each of the @pDescriptorSets@ /must/ be compatible with the pipeline
-- layout specified by @layout@. The layout used to program the bindings
-- /must/ also be compatible with the pipeline used in subsequent
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipeline-bindpoint-commands bound pipeline commands>
-- with that pipeline type, as defined in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility>
-- section.
--
-- The descriptor set contents bound by a call to 'cmdBindDescriptorSets'
-- /may/ be consumed at the following times:
--
-- -   For descriptor bindings created with the
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     bit set, the contents /may/ be consumed when the command buffer is
--     submitted to a queue, or during shader execution of the resulting
--     draws and dispatches, or any time in between. Otherwise,
--
-- -   during host execution of the command, or during shader execution of
--     the resulting draws and dispatches, or any time in between.
--
-- Thus, the contents of a descriptor set binding /must/ not be altered
-- (overwritten by an update command, or freed) between the first point in
-- time that it /may/ be consumed, and when the command completes executing
-- on the queue.
--
-- The contents of @pDynamicOffsets@ are consumed immediately during
-- execution of 'cmdBindDescriptorSets'. Once all pending uses have
-- completed, it is legal to update and reuse a descriptor set.
--
-- == Valid Usage
--
-- -   Each element of @pDescriptorSets@ /must/ have been allocated with a
--     'Vulkan.Core10.Handles.DescriptorSetLayout' that matches (is the
--     same as, or identically defined as) the
--     'Vulkan.Core10.Handles.DescriptorSetLayout' at set /n/ in @layout@,
--     where /n/ is the sum of @firstSet@ and the index into
--     @pDescriptorSets@
--
-- -   @dynamicOffsetCount@ /must/ be equal to the total number of dynamic
--     descriptors in @pDescriptorSets@
--
-- -   The sum of @firstSet@ and @descriptorSetCount@ /must/ be less than
--     or equal to
--     'Vulkan.Core10.PipelineLayout.PipelineLayoutCreateInfo'::@setLayoutCount@
--     provided when @layout@ was created
--
-- -   @pipelineBindPoint@ /must/ be supported by the @commandBuffer@’s
--     parent 'Vulkan.Core10.Handles.CommandPool'’s queue family
--
-- -   Each element of @pDynamicOffsets@ which corresponds to a descriptor
--     binding with type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
--     /must/ be a multiple of
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@minUniformBufferOffsetAlignment@
--
-- -   Each element of @pDynamicOffsets@ which corresponds to a descriptor
--     binding with type
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
--     /must/ be a multiple of
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@minStorageBufferOffsetAlignment@
--
-- -   For each dynamic uniform or storage buffer binding in
--     @pDescriptorSets@, the sum of the effective offset, as defined
--     above, and the range of the binding /must/ be less than or equal to
--     the size of the buffer
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pipelineBindPoint@ /must/ be a valid
--     'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     handle
--
-- -   @pDescriptorSets@ /must/ be a valid pointer to an array of
--     @descriptorSetCount@ valid 'Vulkan.Core10.Handles.DescriptorSet'
--     handles
--
-- -   If @dynamicOffsetCount@ is not @0@, @pDynamicOffsets@ /must/ be a
--     valid pointer to an array of @dynamicOffsetCount@ @uint32_t@ values
--
-- -   @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, or compute operations
--
-- -   @descriptorSetCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @layout@, and the elements of
--     @pDescriptorSets@ /must/ have been created, allocated, or retrieved
--     from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Handles.DescriptorSet',
-- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint',
-- 'Vulkan.Core10.Handles.PipelineLayout'
cmdBindDescriptorSets :: forall io
                       . (MonadIO io)
                      => -- | @commandBuffer@ is the command buffer that the descriptor sets will be
                         -- bound to.
                         CommandBuffer
                      -> -- | @pipelineBindPoint@ is a
                         -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' indicating the
                         -- type of the pipeline that will use the descriptors. There is a separate
                         -- set of bind points for each pipeline type, so binding one does not
                         -- disturb the others.
                         PipelineBindPoint
                      -> -- | @layout@ is a 'Vulkan.Core10.Handles.PipelineLayout' object used to
                         -- program the bindings.
                         PipelineLayout
                      -> -- | @firstSet@ is the set number of the first descriptor set to be bound.
                         ("firstSet" ::: Word32)
                      -> -- | @pDescriptorSets@ is a pointer to an array of handles to
                         -- 'Vulkan.Core10.Handles.DescriptorSet' objects describing the descriptor
                         -- sets to write to.
                         ("descriptorSets" ::: Vector DescriptorSet)
                      -> -- | @pDynamicOffsets@ is a pointer to an array of @uint32_t@ values
                         -- specifying dynamic offsets.
                         ("dynamicOffsets" ::: Vector Word32)
                      -> io ()
cmdBindDescriptorSets :: CommandBuffer
-> PipelineBindPoint
-> PipelineLayout
-> ("firstViewport" ::: Word32)
-> ("descriptorSets" ::: Vector DescriptorSet)
-> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32))
-> io ()
cmdBindDescriptorSets commandBuffer :: CommandBuffer
commandBuffer pipelineBindPoint :: PipelineBindPoint
pipelineBindPoint layout :: PipelineLayout
layout firstSet :: "firstViewport" ::: Word32
firstSet descriptorSets :: "descriptorSets" ::: Vector DescriptorSet
descriptorSets dynamicOffsets :: "dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)
dynamicOffsets = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdBindDescriptorSetsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pDescriptorSets" ::: Ptr DescriptorSet)
   -> ("firstViewport" ::: Word32)
   -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
   -> IO ())
vkCmdBindDescriptorSetsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> PipelineBindPoint
      -> PipelineLayout
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pDescriptorSets" ::: Ptr DescriptorSet)
      -> ("firstViewport" ::: Word32)
      -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
      -> IO ())
pVkCmdBindDescriptorSets (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pDescriptorSets" ::: Ptr DescriptorSet)
   -> ("firstViewport" ::: Word32)
   -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
   -> IO ())
vkCmdBindDescriptorSetsPtr FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pDescriptorSets" ::: Ptr DescriptorSet)
   -> ("firstViewport" ::: Word32)
   -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> PipelineBindPoint
      -> PipelineLayout
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pDescriptorSets" ::: Ptr DescriptorSet)
      -> ("firstViewport" ::: Word32)
      -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pDescriptorSets" ::: Ptr DescriptorSet)
   -> ("firstViewport" ::: Word32)
   -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: 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 vkCmdBindDescriptorSets is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBindDescriptorSets' :: Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pDescriptorSets" ::: Ptr DescriptorSet)
-> ("firstViewport" ::: Word32)
-> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ()
vkCmdBindDescriptorSets' = FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pDescriptorSets" ::: Ptr DescriptorSet)
   -> ("firstViewport" ::: Word32)
   -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
   -> IO ())
-> Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pDescriptorSets" ::: Ptr DescriptorSet)
-> ("firstViewport" ::: Word32)
-> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ()
mkVkCmdBindDescriptorSets FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pDescriptorSets" ::: Ptr DescriptorSet)
   -> ("firstViewport" ::: Word32)
   -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
   -> IO ())
vkCmdBindDescriptorSetsPtr
  "pDescriptorSets" ::: Ptr DescriptorSet
pPDescriptorSets <- ((("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO ())
-> ContT () IO ("pDescriptorSets" ::: Ptr DescriptorSet)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO ())
 -> ContT () IO ("pDescriptorSets" ::: Ptr DescriptorSet))
-> ((("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO ())
-> ContT () IO ("pDescriptorSets" ::: Ptr DescriptorSet)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DescriptorSet ((("descriptorSets" ::: Vector DescriptorSet) -> Int
forall a. Vector a -> Int
Data.Vector.length ("descriptorSets" ::: Vector DescriptorSet
descriptorSets)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DescriptorSet -> IO ())
-> ("descriptorSets" ::: Vector DescriptorSet) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DescriptorSet
e -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> DescriptorSet -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pDescriptorSets" ::: Ptr DescriptorSet
pPDescriptorSets ("pDescriptorSets" ::: Ptr DescriptorSet)
-> Int -> "pDescriptorSets" ::: Ptr DescriptorSet
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorSet) (DescriptorSet
e)) ("descriptorSets" ::: Vector DescriptorSet
descriptorSets)
  "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pPDynamicOffsets <- ((("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
  -> IO ())
 -> IO ())
-> ContT
     () IO ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
   -> IO ())
  -> IO ())
 -> ContT
      () IO ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)))
-> ((("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
     -> IO ())
    -> IO ())
-> ContT
     () IO ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
    -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)
dynamicOffsets)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ("firstViewport" ::: Word32) -> IO ())
-> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32))
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "firstViewport" ::: Word32
e -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pPDynamicOffsets ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: 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) ("firstViewport" ::: Word32
e)) ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)
dynamicOffsets)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pDescriptorSets" ::: Ptr DescriptorSet)
-> ("firstViewport" ::: Word32)
-> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ()
vkCmdBindDescriptorSets' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (PipelineBindPoint
pipelineBindPoint) (PipelineLayout
layout) ("firstViewport" ::: Word32
firstSet) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("descriptorSets" ::: Vector DescriptorSet) -> Int
forall a. Vector a -> Int
Data.Vector.length (("descriptorSets" ::: Vector DescriptorSet) -> Int)
-> ("descriptorSets" ::: Vector DescriptorSet) -> Int
forall a b. (a -> b) -> a -> b
$ ("descriptorSets" ::: Vector DescriptorSet
descriptorSets)) :: Word32)) ("pDescriptorSets" ::: Ptr DescriptorSet
pPDescriptorSets) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int)
-> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32))
-> Int
forall a b. (a -> b) -> a -> b
$ ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)
dynamicOffsets)) :: Word32)) ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pPDynamicOffsets)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBindIndexBuffer
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IndexType -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IndexType -> IO ()

-- | vkCmdBindIndexBuffer - Bind an index buffer to a command buffer
--
-- == Valid Usage
--
-- -   @offset@ /must/ be less than the size of @buffer@
--
-- -   The sum of @offset@ and the address of the range of
--     'Vulkan.Core10.Handles.DeviceMemory' object that is backing
--     @buffer@, /must/ be a multiple of the type indicated by @indexType@
--
-- -   @buffer@ /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDEX_BUFFER_BIT'
--     flag
--
-- -   If @buffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @indexType@ /must/ not be
--     'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_NONE_KHR'
--
-- -   If @indexType@ is
--     'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT8_EXT', the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-indexTypeUint8 indexTypeUint8>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @indexType@ /must/ be a valid
--     'Vulkan.Core10.Enums.IndexType.IndexType' value
--
-- -   @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 operations
--
-- -   Both of @buffer@, and @commandBuffer@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.IndexType.IndexType'
cmdBindIndexBuffer :: forall io
                    . (MonadIO io)
                   => -- | @commandBuffer@ is the command buffer into which the command is
                      -- recorded.
                      CommandBuffer
                   -> -- | @buffer@ is the buffer being bound.
                      Buffer
                   -> -- | @offset@ is the starting offset in bytes within @buffer@ used in index
                      -- buffer address calculations.
                      ("offset" ::: DeviceSize)
                   -> -- | @indexType@ is a 'Vulkan.Core10.Enums.IndexType.IndexType' value
                      -- specifying whether indices are treated as 16 bits or 32 bits.
                      IndexType
                   -> io ()
cmdBindIndexBuffer :: CommandBuffer
-> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> io ()
cmdBindIndexBuffer commandBuffer :: CommandBuffer
commandBuffer buffer :: Buffer
buffer offset :: "offset" ::: DeviceSize
offset indexType :: IndexType
indexType = 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 vkCmdBindIndexBufferPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
vkCmdBindIndexBufferPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
pVkCmdBindIndexBuffer (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
vkCmdBindIndexBufferPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> 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 vkCmdBindIndexBuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBindIndexBuffer' :: Ptr CommandBuffer_T
-> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()
vkCmdBindIndexBuffer' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> IndexType
-> IO ()
mkVkCmdBindIndexBuffer FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ())
vkCmdBindIndexBufferPtr
  Ptr CommandBuffer_T
-> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()
vkCmdBindIndexBuffer' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
buffer) ("offset" ::: DeviceSize
offset) (IndexType
indexType)
  () -> 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" mkVkCmdBindVertexBuffers
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Buffer -> Ptr DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Buffer -> Ptr DeviceSize -> IO ()

-- | vkCmdBindVertexBuffers - Bind vertex buffers to a command buffer
--
-- = Description
--
-- The values taken from elements i of @pBuffers@ and @pOffsets@ replace
-- the current state for the vertex input binding @firstBinding@ + i, for i
-- in [0, @bindingCount@). The vertex input binding is updated to start at
-- the offset indicated by @pOffsets@[i] from the start of the buffer
-- @pBuffers@[i]. All vertex input attributes that use each of these
-- bindings will use these updated addresses in their address calculations
-- for subsequent draw commands. If the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor>
-- feature is enabled, elements of @pBuffers@ /can/ be
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and /can/ be used by the
-- vertex shader. If a vertex input attribute is bound to a vertex input
-- binding that is 'Vulkan.Core10.APIConstants.NULL_HANDLE', the values
-- taken from memory are considered to be zero, and missing G, B, or A
-- components are
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input-extraction filled with (0,0,1)>.
--
-- == Valid Usage
--
-- -   @firstBinding@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@
--
-- -   The sum of @firstBinding@ and @bindingCount@ /must/ be less than or
--     equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@
--
-- -   All elements of @pOffsets@ /must/ be less than the size of the
--     corresponding element in @pBuffers@
--
-- -   All elements of @pBuffers@ /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_VERTEX_BUFFER_BIT'
--     flag
--
-- -   Each element of @pBuffers@ that is non-sparse /must/ be bound
--     completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor>
--     feature is not enabled, all elements of @pBuffers@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If an element of @pBuffers@ is
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', then the corresponding
--     element of @pOffsets@ /must/ be zero
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pBuffers@ /must/ be a valid pointer to an array of @bindingCount@
--     valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--     'Vulkan.Core10.Handles.Buffer' handles
--
-- -   @pOffsets@ /must/ be a valid pointer to an array of @bindingCount@
--     'Vulkan.Core10.FundamentalTypes.DeviceSize' values
--
-- -   @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 operations
--
-- -   @bindingCount@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and the elements of @pBuffers@ that are
--     valid handles of non-ignored parameters /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdBindVertexBuffers :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command is
                        -- recorded.
                        CommandBuffer
                     -> -- | @firstBinding@ is the index of the first vertex input binding whose
                        -- state is updated by the command.
                        ("firstBinding" ::: Word32)
                     -> -- | @pBuffers@ is a pointer to an array of buffer handles.
                        ("buffers" ::: Vector Buffer)
                     -> -- | @pOffsets@ is a pointer to an array of buffer offsets.
                        ("offsets" ::: Vector DeviceSize)
                     -> io ()
cmdBindVertexBuffers :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("buffers" ::: Vector Buffer)
-> ("offsets" ::: Vector ("offset" ::: DeviceSize))
-> io ()
cmdBindVertexBuffers commandBuffer :: CommandBuffer
commandBuffer firstBinding :: "firstViewport" ::: Word32
firstBinding buffers :: "buffers" ::: Vector Buffer
buffers offsets :: "offsets" ::: Vector ("offset" ::: DeviceSize)
offsets = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdBindVertexBuffersPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pBuffers" ::: Ptr Buffer)
   -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
   -> IO ())
vkCmdBindVertexBuffersPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pBuffers" ::: Ptr Buffer)
      -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
      -> IO ())
pVkCmdBindVertexBuffers (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pBuffers" ::: Ptr Buffer)
   -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
   -> IO ())
vkCmdBindVertexBuffersPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pBuffers" ::: Ptr Buffer)
   -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pBuffers" ::: Ptr Buffer)
      -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pBuffers" ::: Ptr Buffer)
   -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
   -> 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 vkCmdBindVertexBuffers is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBindVertexBuffers' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pBuffers" ::: Ptr Buffer)
-> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
vkCmdBindVertexBuffers' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pBuffers" ::: Ptr Buffer)
   -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pBuffers" ::: Ptr Buffer)
-> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
mkVkCmdBindVertexBuffers FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pBuffers" ::: Ptr Buffer)
   -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
   -> IO ())
vkCmdBindVertexBuffersPtr
  let pBuffersLength :: Int
pBuffersLength = ("buffers" ::: Vector Buffer) -> Int
forall a. Vector a -> Int
Data.Vector.length (("buffers" ::: Vector Buffer) -> Int)
-> ("buffers" ::: Vector Buffer) -> Int
forall a b. (a -> b) -> a -> b
$ ("buffers" ::: Vector Buffer
buffers)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int)
-> ("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int
forall a b. (a -> b) -> a -> b
$ ("offsets" ::: Vector ("offset" ::: DeviceSize)
offsets)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pBuffersLength) (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 "" "pOffsets and pBuffers must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  "pBuffers" ::: Ptr Buffer
pPBuffers <- ((("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ())
-> ContT () IO ("pBuffers" ::: Ptr Buffer)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ())
 -> ContT () IO ("pBuffers" ::: Ptr Buffer))
-> ((("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ())
-> ContT () IO ("pBuffers" ::: Ptr Buffer)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Buffer ((("buffers" ::: Vector Buffer) -> Int
forall a. Vector a -> Int
Data.Vector.length ("buffers" ::: Vector Buffer
buffers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Buffer -> IO ()) -> ("buffers" ::: Vector Buffer) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Buffer
e -> ("pBuffers" ::: Ptr Buffer) -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pBuffers" ::: Ptr Buffer
pPBuffers ("pBuffers" ::: Ptr Buffer) -> Int -> "pBuffers" ::: Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Buffer) (Buffer
e)) ("buffers" ::: Vector Buffer
buffers)
  "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
pPOffsets <- ((("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ())
 -> IO ())
-> ContT () IO ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ())
  -> IO ())
 -> ContT () IO ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)))
-> ((("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ())
    -> IO ())
-> ContT () IO ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceSize ((("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("offsets" ::: Vector ("offset" ::: DeviceSize)
offsets)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ("offset" ::: DeviceSize) -> IO ())
-> ("offsets" ::: Vector ("offset" ::: DeviceSize)) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "offset" ::: DeviceSize
e -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)
pPOffsets ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) ("offset" ::: DeviceSize
e)) ("offsets" ::: Vector ("offset" ::: DeviceSize)
offsets)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pBuffers" ::: Ptr Buffer)
-> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
vkCmdBindVertexBuffers' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstViewport" ::: Word32
firstBinding) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pBuffersLength :: Word32)) ("pBuffers" ::: Ptr Buffer
pPBuffers) ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)
pPOffsets)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdDraw - Draw primitives
--
-- = Description
--
-- When the command is executed, primitives are assembled using the current
-- primitive topology and @vertexCount@ consecutive vertex indices with the
-- first @vertexIndex@ value equal to @firstVertex@. The primitives are
-- drawn @instanceCount@ times with @instanceIndex@ starting with
-- @firstInstance@ and increasing sequentially for each instance. The
-- assembled primitives execute the bound graphics pipeline.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' 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
--     '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.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' 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.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   The current render pass /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible>
--     with the @renderPass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   The subpass index of the current render pass /must/ be equal to the
--     @subpass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   Every input attachment used by the current subpass /must/ be bound
--     to the pipeline via a descriptor set
--
-- -   Image subresources used as attachments in the current render pass
--     /must/ not be accessed in any way other than as an attachment by
--     this command
--
-- -   If the draw is recorded in a render pass instance with multiview
--     enabled, the maximum instance index /must/ be less than or equal to
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@
--
-- -   If the bound graphics pipeline was created with
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@
--     set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass
--     has a depth\/stencil attachment, then that attachment /must/ have
--     been created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT'
--     bit set
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with both the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic states enabled then both
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     and
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT'
--     dynamic state enabled then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @primitiveTopology@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ be of the same
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class>
--     as the pipeline
--     'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@
--     state
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported, the bound graphics pipeline was created with
--     the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, and any of the shader stages of the bound
--     graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in,
--     then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ be @1@
--
-- -   If @commandBuffer@ is a protected command buffer, any resource
--     written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to
--     the pipeline bind point used by this command /must/ not be an
--     unprotected resource
--
-- -   If @commandBuffer@ is a protected command buffer, pipeline stages
--     other than the framebuffer-space and compute stages in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point /must/ not write to any resource
--
-- -   All vertex input bindings accessed via vertex input variables
--     declared in the vertex shader entry point’s interface /must/ have
--     either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers
--     bound
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor>
--     feature is not enabled, all vertex input bindings accessed via
--     vertex input variables declared in the vertex shader entry point’s
--     interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   For a given vertex buffer binding, any attribute data fetched /must/
--     be entirely contained within the corresponding vertex buffer
--     binding, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???>
--
-- == 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 operations
--
-- -   This command /must/ only be called inside 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdDraw :: forall io
         . (MonadIO io)
        => -- | @commandBuffer@ is the command buffer into which the command is
           -- recorded.
           CommandBuffer
        -> -- | @vertexCount@ is the number of vertices to draw.
           ("vertexCount" ::: Word32)
        -> -- | @instanceCount@ is the number of instances to draw.
           ("instanceCount" ::: Word32)
        -> -- | @firstVertex@ is the index of the first vertex to draw.
           ("firstVertex" ::: Word32)
        -> -- | @firstInstance@ is the instance ID of the first instance to draw.
           ("firstInstance" ::: Word32)
        -> io ()
cmdDraw :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> io ()
cmdDraw commandBuffer :: CommandBuffer
commandBuffer vertexCount :: "firstViewport" ::: Word32
vertexCount instanceCount :: "firstViewport" ::: Word32
instanceCount firstVertex :: "firstViewport" ::: Word32
firstVertex firstInstance :: "firstViewport" ::: Word32
firstInstance = 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 vkCmdDrawPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdDraw (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: 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 vkCmdDraw is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDraw' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDraw' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdDraw FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawPtr
  Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDraw' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstViewport" ::: Word32
vertexCount) ("firstViewport" ::: Word32
instanceCount) ("firstViewport" ::: Word32
firstVertex) ("firstViewport" ::: Word32
firstInstance)
  () -> 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" mkVkCmdDrawIndexed
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Int32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Int32 -> Word32 -> IO ()

-- | vkCmdDrawIndexed - Issue an indexed draw into a command buffer
--
-- = Description
--
-- When the command is executed, primitives are assembled using the current
-- primitive topology and @indexCount@ vertices whose indices are retrieved
-- from the index buffer. The index buffer is treated as an array of
-- tightly packed unsigned integers of size defined by the
-- 'cmdBindIndexBuffer'::@indexType@ parameter with which the buffer was
-- bound.
--
-- The first vertex index is at an offset of @firstIndex@ × @indexSize@ +
-- @offset@ within the bound index buffer, where @offset@ is the offset
-- specified by 'cmdBindIndexBuffer' and @indexSize@ is the byte size of
-- the type specified by @indexType@. Subsequent index values are retrieved
-- from consecutive locations in the index buffer. Indices are first
-- compared to the primitive restart value, then zero extended to 32 bits
-- (if the @indexType@ is
-- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT8_EXT' or
-- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT16') and have
-- @vertexOffset@ added to them, before being supplied as the @vertexIndex@
-- value.
--
-- The primitives are drawn @instanceCount@ times with @instanceIndex@
-- starting with @firstInstance@ and increasing sequentially for each
-- instance. The assembled primitives execute the bound graphics pipeline.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' 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
--     '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.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' 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.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   The current render pass /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible>
--     with the @renderPass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   The subpass index of the current render pass /must/ be equal to the
--     @subpass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   Every input attachment used by the current subpass /must/ be bound
--     to the pipeline via a descriptor set
--
-- -   Image subresources used as attachments in the current render pass
--     /must/ not be accessed in any way other than as an attachment by
--     this command
--
-- -   If the draw is recorded in a render pass instance with multiview
--     enabled, the maximum instance index /must/ be less than or equal to
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@
--
-- -   If the bound graphics pipeline was created with
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@
--     set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass
--     has a depth\/stencil attachment, then that attachment /must/ have
--     been created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT'
--     bit set
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with both the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic states enabled then both
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     and
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT'
--     dynamic state enabled then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @primitiveTopology@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ be of the same
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class>
--     as the pipeline
--     'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@
--     state
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported, the bound graphics pipeline was created with
--     the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, and any of the shader stages of the bound
--     graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in,
--     then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ be @1@
--
-- -   If @commandBuffer@ is a protected command buffer, any resource
--     written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to
--     the pipeline bind point used by this command /must/ not be an
--     unprotected resource
--
-- -   If @commandBuffer@ is a protected command buffer, pipeline stages
--     other than the framebuffer-space and compute stages in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point /must/ not write to any resource
--
-- -   All vertex input bindings accessed via vertex input variables
--     declared in the vertex shader entry point’s interface /must/ have
--     either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers
--     bound
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor>
--     feature is not enabled, all vertex input bindings accessed via
--     vertex input variables declared in the vertex shader entry point’s
--     interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   For a given vertex buffer binding, any attribute data fetched /must/
--     be entirely contained within the corresponding vertex buffer
--     binding, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???>
--
-- -   (@indexSize@ × (@firstIndex@ + @indexCount@) + @offset@) /must/ be
--     less than or equal to the size of the bound index buffer, with
--     @indexSize@ being based on the type specified by @indexType@, where
--     the index buffer, @indexType@, and @offset@ are specified via
--     'cmdBindIndexBuffer'
--
-- == 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 operations
--
-- -   This command /must/ only be called inside 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdDrawIndexed :: forall io
                . (MonadIO io)
               => -- | @commandBuffer@ is the command buffer into which the command is
                  -- recorded.
                  CommandBuffer
               -> -- | @indexCount@ is the number of vertices to draw.
                  ("indexCount" ::: Word32)
               -> -- | @instanceCount@ is the number of instances to draw.
                  ("instanceCount" ::: Word32)
               -> -- | @firstIndex@ is the base index within the index buffer.
                  ("firstIndex" ::: Word32)
               -> -- | @vertexOffset@ is the value added to the vertex index before indexing
                  -- into the vertex buffer.
                  ("vertexOffset" ::: Int32)
               -> -- | @firstInstance@ is the instance ID of the first instance to draw.
                  ("firstInstance" ::: Word32)
               -> io ()
cmdDrawIndexed :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("vertexOffset" ::: Int32)
-> ("firstViewport" ::: Word32)
-> io ()
cmdDrawIndexed commandBuffer :: CommandBuffer
commandBuffer indexCount :: "firstViewport" ::: Word32
indexCount instanceCount :: "firstViewport" ::: Word32
instanceCount firstIndex :: "firstViewport" ::: Word32
firstIndex vertexOffset :: "vertexOffset" ::: Int32
vertexOffset firstInstance :: "firstViewport" ::: Word32
firstInstance = 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 vkCmdDrawIndexedPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("vertexOffset" ::: Int32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndexedPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("vertexOffset" ::: Int32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdDrawIndexed (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("vertexOffset" ::: Int32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndexedPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("vertexOffset" ::: Int32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("vertexOffset" ::: Int32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("vertexOffset" ::: Int32)
   -> ("firstViewport" ::: 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 vkCmdDrawIndexed is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDrawIndexed' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("vertexOffset" ::: Int32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDrawIndexed' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("vertexOffset" ::: Int32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("vertexOffset" ::: Int32)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdDrawIndexed FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("vertexOffset" ::: Int32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndexedPtr
  Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("vertexOffset" ::: Int32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDrawIndexed' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstViewport" ::: Word32
indexCount) ("firstViewport" ::: Word32
instanceCount) ("firstViewport" ::: Word32
firstIndex) ("vertexOffset" ::: Int32
vertexOffset) ("firstViewport" ::: Word32
firstInstance)
  () -> 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" mkVkCmdDrawIndirect
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()

-- | vkCmdDrawIndirect - Issue an indirect draw into a command buffer
--
-- = Description
--
-- 'cmdDrawIndirect' behaves similarly to 'cmdDraw' except that the
-- parameters are read by the device from a buffer during execution.
-- @drawCount@ draws are executed by the command, with parameters taken
-- from @buffer@ starting at @offset@ and increasing by @stride@ bytes for
-- each successive draw. The parameters of each draw are encoded in an
-- array of 'Vulkan.Core10.OtherTypes.DrawIndirectCommand' structures. If
-- @drawCount@ is less than or equal to one, @stride@ is ignored.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' 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
--     '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.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' 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.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   The current render pass /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible>
--     with the @renderPass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   The subpass index of the current render pass /must/ be equal to the
--     @subpass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   Every input attachment used by the current subpass /must/ be bound
--     to the pipeline via a descriptor set
--
-- -   Image subresources used as attachments in the current render pass
--     /must/ not be accessed in any way other than as an attachment by
--     this command
--
-- -   If the draw is recorded in a render pass instance with multiview
--     enabled, the maximum instance index /must/ be less than or equal to
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@
--
-- -   If the bound graphics pipeline was created with
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@
--     set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass
--     has a depth\/stencil attachment, then that attachment /must/ have
--     been created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT'
--     bit set
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with both the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic states enabled then both
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     and
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT'
--     dynamic state enabled then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @primitiveTopology@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ be of the same
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class>
--     as the pipeline
--     'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@
--     state
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported, the bound graphics pipeline was created with
--     the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, and any of the shader stages of the bound
--     graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in,
--     then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ be @1@
--
-- -   All vertex input bindings accessed via vertex input variables
--     declared in the vertex shader entry point’s interface /must/ have
--     either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers
--     bound
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor>
--     feature is not enabled, all vertex input bindings accessed via
--     vertex input variables declared in the vertex shader entry point’s
--     interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   For a given vertex buffer binding, any attribute data fetched /must/
--     be entirely contained within the corresponding vertex buffer
--     binding, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???>
--
-- -   If @buffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @buffer@ /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT'
--     bit set
--
-- -   @offset@ /must/ be a multiple of @4@
--
-- -   @commandBuffer@ /must/ not be a protected command buffer
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multi-draw indirect>
--     feature is not enabled, @drawCount@ /must/ be @0@ or @1@
--
-- -   @drawCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDrawIndirectCount@
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-drawIndirectFirstInstance drawIndirectFirstInstance>
--     feature is not enabled, all the @firstInstance@ members of the
--     'Vulkan.Core10.OtherTypes.DrawIndirectCommand' structures accessed
--     by this command /must/ be @0@
--
-- -   If @drawCount@ is greater than @1@, @stride@ /must/ be a multiple of
--     @4@ and /must/ be greater than or equal to
--     @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand')
--
-- -   If @drawCount@ is equal to @1@, (@offset@ +
--     @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand')) /must/ be
--     less than or equal to the size of @buffer@
--
-- -   If @drawCount@ is greater than @1@, (@stride@ × (@drawCount@ - 1) +
--     @offset@ + @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand'))
--     /must/ be less than or equal to the size of @buffer@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' 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 operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   Both of @buffer@, and @commandBuffer@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdDrawIndirect :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command is
                   -- recorded.
                   CommandBuffer
                -> -- | @buffer@ is the buffer containing draw parameters.
                   Buffer
                -> -- | @offset@ is the byte offset into @buffer@ where parameters begin.
                   ("offset" ::: DeviceSize)
                -> -- | @drawCount@ is the number of draws to execute, and /can/ be zero.
                   ("drawCount" ::: Word32)
                -> -- | @stride@ is the byte stride between successive sets of draw parameters.
                   ("stride" ::: Word32)
                -> io ()
cmdDrawIndirect :: CommandBuffer
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> io ()
cmdDrawIndirect commandBuffer :: CommandBuffer
commandBuffer buffer :: Buffer
buffer offset :: "offset" ::: DeviceSize
offset drawCount :: "firstViewport" ::: Word32
drawCount stride :: "firstViewport" ::: Word32
stride = 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 vkCmdDrawIndirectPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndirectPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdDrawIndirect (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndirectPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: 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 vkCmdDrawIndirect is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDrawIndirect' :: Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDrawIndirect' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdDrawIndirect FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndirectPtr
  Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDrawIndirect' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
buffer) ("offset" ::: DeviceSize
offset) ("firstViewport" ::: Word32
drawCount) ("firstViewport" ::: Word32
stride)
  () -> 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" mkVkCmdDrawIndexedIndirect
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()

-- | vkCmdDrawIndexedIndirect - Perform an indexed indirect draw
--
-- = Description
--
-- 'cmdDrawIndexedIndirect' behaves similarly to 'cmdDrawIndexed' except
-- that the parameters are read by the device from a buffer during
-- execution. @drawCount@ draws are executed by the command, with
-- parameters taken from @buffer@ starting at @offset@ and increasing by
-- @stride@ bytes for each successive draw. The parameters of each draw are
-- encoded in an array of
-- 'Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand' structures. If
-- @drawCount@ is less than or equal to one, @stride@ is ignored.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' 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
--     '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.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' 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.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   The current render pass /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible>
--     with the @renderPass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   The subpass index of the current render pass /must/ be equal to the
--     @subpass@ member of the
--     'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure
--     specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound
--     to
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   Every input attachment used by the current subpass /must/ be bound
--     to the pipeline via a descriptor set
--
-- -   Image subresources used as attachments in the current render pass
--     /must/ not be accessed in any way other than as an attachment by
--     this command
--
-- -   If the draw is recorded in a render pass instance with multiview
--     enabled, the maximum instance index /must/ be less than or equal to
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@
--
-- -   If the bound graphics pipeline was created with
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@
--     set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass
--     has a depth\/stencil attachment, then that attachment /must/ have
--     been created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT'
--     bit set
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ match the
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@
--     of the pipeline
--
-- -   If the bound graphics pipeline state was created with both the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic states enabled then both
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     and
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ match the @scissorCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, but not the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic state enabled, then the bound graphics pipeline /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV'
--     dynamic states enabled then the @viewportCount@ parameter in the
--     last call to
--     'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV'
--     /must/ be greater than or equal to the @viewportCount@ parameter in
--     the last call to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled and an instance of
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
--     chained from @VkPipelineVieportCreateInfo@, then the bound graphics
--     pipeline /must/ have been created with
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@
--     greater or equal to the @viewportCount@ parameter in the last call
--     to
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--
-- -   If the bound graphics pipeline state was created with the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT'
--     dynamic state enabled then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @primitiveTopology@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
--     /must/ be of the same
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class>
--     as the pipeline
--     'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@
--     state
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported, the bound graphics pipeline was created with
--     the
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     dynamic state enabled, and any of the shader stages of the bound
--     graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in,
--     then
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ have been called in the current command buffer prior to this
--     draw command, and the @viewportCount@ parameter of
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
--     /must/ be @1@
--
-- -   All vertex input bindings accessed via vertex input variables
--     declared in the vertex shader entry point’s interface /must/ have
--     either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers
--     bound
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor>
--     feature is not enabled, all vertex input bindings accessed via
--     vertex input variables declared in the vertex shader entry point’s
--     interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   For a given vertex buffer binding, any attribute data fetched /must/
--     be entirely contained within the corresponding vertex buffer
--     binding, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???>
--
-- -   If @buffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @buffer@ /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT'
--     bit set
--
-- -   @offset@ /must/ be a multiple of @4@
--
-- -   @commandBuffer@ /must/ not be a protected command buffer
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multi-draw indirect>
--     feature is not enabled, @drawCount@ /must/ be @0@ or @1@
--
-- -   @drawCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDrawIndirectCount@
--
-- -   If @drawCount@ is greater than @1@, @stride@ /must/ be a multiple of
--     @4@ and /must/ be greater than or equal to
--     @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand')
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-drawIndirectFirstInstance drawIndirectFirstInstance>
--     feature is not enabled, all the @firstInstance@ members of the
--     'Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand' structures
--     accessed by this command /must/ be @0@
--
-- -   If @drawCount@ is equal to @1@, (@offset@ +
--     @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand'))
--     /must/ be less than or equal to the size of @buffer@
--
-- -   If @drawCount@ is greater than @1@, (@stride@ × (@drawCount@ - 1) +
--     @offset@ +
--     @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand'))
--     /must/ be less than or equal to the size of @buffer@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' 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 operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   Both of @buffer@, and @commandBuffer@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdDrawIndexedIndirect :: forall io
                        . (MonadIO io)
                       => -- | @commandBuffer@ is the command buffer into which the command is
                          -- recorded.
                          CommandBuffer
                       -> -- | @buffer@ is the buffer containing draw parameters.
                          Buffer
                       -> -- | @offset@ is the byte offset into @buffer@ where parameters begin.
                          ("offset" ::: DeviceSize)
                       -> -- | @drawCount@ is the number of draws to execute, and /can/ be zero.
                          ("drawCount" ::: Word32)
                       -> -- | @stride@ is the byte stride between successive sets of draw parameters.
                          ("stride" ::: Word32)
                       -> io ()
cmdDrawIndexedIndirect :: CommandBuffer
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> io ()
cmdDrawIndexedIndirect commandBuffer :: CommandBuffer
commandBuffer buffer :: Buffer
buffer offset :: "offset" ::: DeviceSize
offset drawCount :: "firstViewport" ::: Word32
drawCount stride :: "firstViewport" ::: Word32
stride = 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 vkCmdDrawIndexedIndirectPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndexedIndirectPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdDrawIndexedIndirect (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndexedIndirectPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: 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 vkCmdDrawIndexedIndirect is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDrawIndexedIndirect' :: Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDrawIndexedIndirect' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdDrawIndexedIndirect FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDrawIndexedIndirectPtr
  Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDrawIndexedIndirect' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
buffer) ("offset" ::: DeviceSize
offset) ("firstViewport" ::: Word32
drawCount) ("firstViewport" ::: Word32
stride)
  () -> 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" mkVkCmdDispatch
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> IO ()

-- | vkCmdDispatch - Dispatch compute work items
--
-- = Description
--
-- When the command is executed, a global workgroup consisting of
-- @groupCountX@ × @groupCountY@ × @groupCountZ@ local workgroups is
-- assembled.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' 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
--     '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.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' 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.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If @commandBuffer@ is a protected command buffer, any resource
--     written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to
--     the pipeline bind point used by this command /must/ not be an
--     unprotected resource
--
-- -   If @commandBuffer@ is a protected command buffer, pipeline stages
--     other than the framebuffer-space and compute stages in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point /must/ not write to any resource
--
-- -   @groupCountX@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0]
--
-- -   @groupCountY@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1]
--
-- -   @groupCountZ@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2]
--
-- == 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                                                                                                               | Compute                                                                                                                             |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdDispatch :: forall io
             . (MonadIO io)
            => -- | @commandBuffer@ is the command buffer into which the command will be
               -- recorded.
               CommandBuffer
            -> -- | @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 ()
cmdDispatch :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> io ()
cmdDispatch commandBuffer :: CommandBuffer
commandBuffer groupCountX :: "firstViewport" ::: Word32
groupCountX groupCountY :: "firstViewport" ::: Word32
groupCountY groupCountZ :: "firstViewport" ::: 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 vkCmdDispatchPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDispatchPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdDispatch (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDispatchPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: 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 vkCmdDispatch is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDispatch' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDispatch' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdDispatch FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdDispatchPtr
  Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdDispatch' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstViewport" ::: Word32
groupCountX) ("firstViewport" ::: Word32
groupCountY) ("firstViewport" ::: Word32
groupCountZ)
  () -> 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" mkVkCmdDispatchIndirect
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IO ()

-- | vkCmdDispatchIndirect - Dispatch compute work items using indirect
-- parameters
--
-- = Description
--
-- 'cmdDispatchIndirect' behaves similarly to 'cmdDispatch' except that the
-- parameters are read by the device from a buffer during execution. The
-- parameters of the dispatch are encoded in a
-- 'Vulkan.Core10.OtherTypes.DispatchIndirectCommand' structure taken from
-- @buffer@ starting at @offset@.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' 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
--     '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.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' 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.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If @buffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @buffer@ /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT'
--     bit set
--
-- -   @offset@ /must/ be a multiple of @4@
--
-- -   @commandBuffer@ /must/ not be a protected command buffer
--
-- -   The sum of @offset@ and the size of
--     'Vulkan.Core10.OtherTypes.DispatchIndirectCommand' /must/ be less
--     than or equal to the size of @buffer@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' 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
--
-- -   Both of @buffer@, and @commandBuffer@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               | Compute                                                                                                                             |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdDispatchIndirect :: forall io
                     . (MonadIO io)
                    => -- | @commandBuffer@ is the command buffer into which the command will be
                       -- recorded.
                       CommandBuffer
                    -> -- | @buffer@ is the buffer containing dispatch parameters.
                       Buffer
                    -> -- | @offset@ is the byte offset into @buffer@ where parameters begin.
                       ("offset" ::: DeviceSize)
                    -> io ()
cmdDispatchIndirect :: CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> io ()
cmdDispatchIndirect commandBuffer :: CommandBuffer
commandBuffer buffer :: Buffer
buffer offset :: "offset" ::: DeviceSize
offset = 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 vkCmdDispatchIndirectPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
vkCmdDispatchIndirectPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
pVkCmdDispatchIndirect (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
vkCmdDispatchIndirectPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> 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 vkCmdDispatchIndirect is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDispatchIndirect' :: Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()
vkCmdDispatchIndirect' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> IO ()
mkVkCmdDispatchIndirect FunPtr
  (Ptr CommandBuffer_T
   -> Buffer -> ("offset" ::: DeviceSize) -> IO ())
vkCmdDispatchIndirectPtr
  Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()
vkCmdDispatchIndirect' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
buffer) ("offset" ::: DeviceSize
offset)
  () -> 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" mkVkCmdCopyBuffer
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> Word32 -> Ptr BufferCopy -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> Buffer -> Word32 -> Ptr BufferCopy -> IO ()

-- | vkCmdCopyBuffer - Copy data between buffer regions
--
-- = Description
--
-- Each region in @pRegions@ is copied from the source buffer to the same
-- region of the destination buffer. @srcBuffer@ and @dstBuffer@ /can/ be
-- the same buffer or alias the same memory, but the resulting values are
-- undefined if the copy regions overlap in memory.
--
-- == Valid Usage
--
-- -   If @commandBuffer@ is an unprotected command buffer, then
--     @srcBuffer@ /must/ not be a protected buffer
--
-- -   If @commandBuffer@ is an unprotected command buffer, then
--     @dstBuffer@ /must/ not be a protected buffer
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstBuffer@
--     /must/ not be an unprotected buffer
--
-- -   The @srcOffset@ member of each element of @pRegions@ /must/ be less
--     than the size of @srcBuffer@
--
-- -   The @dstOffset@ member of each element of @pRegions@ /must/ be less
--     than the size of @dstBuffer@
--
-- -   The @size@ member of each element of @pRegions@ /must/ be less than
--     or equal to the size of @srcBuffer@ minus @srcOffset@
--
-- -   The @size@ member of each element of @pRegions@ /must/ be less than
--     or equal to the size of @dstBuffer@ minus @dstOffset@
--
-- -   The union of the source regions, and the union of the destination
--     regions, specified by the elements of @pRegions@, /must/ not overlap
--     in memory
--
-- -   @srcBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_SRC_BIT'
--     usage flag
--
-- -   If @srcBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @dstBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @pRegions@ /must/ be a valid pointer to an array of @regionCount@
--     valid 'BufferCopy' structures
--
-- -   @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 transfer, graphics, or compute
--     operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @regionCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @dstBuffer@, and @srcBuffer@ /must/ have
--     been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'BufferCopy',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdCopyBuffer :: forall io
               . (MonadIO io)
              => -- | @commandBuffer@ is the command buffer into which the command will be
                 -- recorded.
                 CommandBuffer
              -> -- | @srcBuffer@ is the source buffer.
                 ("srcBuffer" ::: Buffer)
              -> -- | @dstBuffer@ is the destination buffer.
                 ("dstBuffer" ::: Buffer)
              -> -- | @pRegions@ is a pointer to an array of 'BufferCopy' structures
                 -- specifying the regions to copy.
                 ("regions" ::: Vector BufferCopy)
              -> io ()
cmdCopyBuffer :: CommandBuffer
-> Buffer -> Buffer -> ("regions" ::: Vector BufferCopy) -> io ()
cmdCopyBuffer commandBuffer :: CommandBuffer
commandBuffer srcBuffer :: Buffer
srcBuffer dstBuffer :: Buffer
dstBuffer regions :: "regions" ::: Vector BufferCopy
regions = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyBufferPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferCopy)
   -> IO ())
vkCmdCopyBufferPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> Buffer
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr BufferCopy)
      -> IO ())
pVkCmdCopyBuffer (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferCopy)
   -> IO ())
vkCmdCopyBufferPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferCopy)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> Buffer
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr BufferCopy)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferCopy)
   -> 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 vkCmdCopyBuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyBuffer' :: Ptr CommandBuffer_T
-> Buffer
-> Buffer
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferCopy)
-> IO ()
vkCmdCopyBuffer' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferCopy)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> Buffer
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferCopy)
-> IO ()
mkVkCmdCopyBuffer FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferCopy)
   -> IO ())
vkCmdCopyBufferPtr
  "pRegions" ::: Ptr BufferCopy
pPRegions <- ((("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr BufferCopy)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ())
 -> ContT () IO ("pRegions" ::: Ptr BufferCopy))
-> ((("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr BufferCopy)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @BufferCopy ((("regions" ::: Vector BufferCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length ("regions" ::: Vector BufferCopy
regions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
  (Int -> BufferCopy -> ContT () IO ())
-> ("regions" ::: Vector BufferCopy) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: BufferCopy
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRegions" ::: Ptr BufferCopy) -> BufferCopy -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRegions" ::: Ptr BufferCopy
pPRegions ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pRegions" ::: Ptr BufferCopy
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr BufferCopy) (BufferCopy
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("regions" ::: Vector BufferCopy
regions)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> Buffer
-> Buffer
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferCopy)
-> IO ()
vkCmdCopyBuffer' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
srcBuffer) (Buffer
dstBuffer) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("regions" ::: Vector BufferCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length (("regions" ::: Vector BufferCopy) -> Int)
-> ("regions" ::: Vector BufferCopy) -> Int
forall a b. (a -> b) -> a -> b
$ ("regions" ::: Vector BufferCopy
regions)) :: Word32)) ("pRegions" ::: Ptr BufferCopy
pPRegions)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdCopyImage - Copy data between images
--
-- = Description
--
-- Each region in @pRegions@ is copied from the source image to the same
-- region of the destination image. @srcImage@ and @dstImage@ /can/ be the
-- same image or alias the same memory.
--
-- The formats of @srcImage@ and @dstImage@ /must/ be compatible. Formats
-- are compatible if they share the same class, as shown in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility Compatible Formats>
-- table. Depth\/stencil formats /must/ match exactly.
--
-- If the format of @srcImage@ or @dstImage@ is a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>,
-- regions of each plane to be copied /must/ be specified separately using
-- the @srcSubresource@ and @dstSubresource@ members of the 'ImageCopy'
-- structure. In this case, the @aspectMask@ of the @srcSubresource@ or
-- @dstSubresource@ that refers to the multi-planar image /must/ be
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', or
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'. For
-- the purposes of 'cmdCopyImage', each plane of a multi-planar image is
-- treated as having the format listed in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes>
-- for the plane identified by the @aspectMask@ of the corresponding
-- subresource. This applies both to 'Vulkan.Core10.Enums.Format.Format'
-- and to coordinates used in the copy, which correspond to texels in the
-- /plane/ rather than how these texels map to coordinates in the image as
-- a whole.
--
-- Note
--
-- For example, the
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' plane
-- of a 'Vulkan.Core10.Enums.Format.FORMAT_G8_B8R8_2PLANE_420_UNORM' image
-- is compatible with an image of format
-- 'Vulkan.Core10.Enums.Format.FORMAT_R8G8_UNORM' and (less usefully) with
-- the 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- plane of an image of format
-- 'Vulkan.Core10.Enums.Format.FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16',
-- as each texel is 2 bytes in size.
--
-- 'cmdCopyImage' allows copying between /size-compatible/ compressed and
-- uncompressed internal formats. Formats are size-compatible if the texel
-- block size of the uncompressed format is equal to the texel block size
-- of the compressed format. Such a copy does not perform on-the-fly
-- compression or decompression. When copying from an uncompressed format
-- to a compressed format, each texel of uncompressed data of the source
-- image is copied as a raw value to the corresponding compressed texel
-- block of the destination image. When copying from a compressed format to
-- an uncompressed format, each compressed texel block of the source image
-- is copied as a raw value to the corresponding texel of uncompressed data
-- in the destination image. Thus, for example, it is legal to copy between
-- a 128-bit uncompressed format and a compressed format which has a
-- 128-bit sized compressed texel block representing 4×4 texels (using 8
-- bits per texel), or between a 64-bit uncompressed format and a
-- compressed format which has a 64-bit sized compressed texel block
-- representing 4×4 texels (using 4 bits per texel).
--
-- When copying between compressed and uncompressed formats the @extent@
-- members represent the texel dimensions of the source image and not the
-- destination. When copying from a compressed image to an uncompressed
-- image the image texel dimensions written to the uncompressed image will
-- be source extent divided by the compressed texel block dimensions. When
-- copying from an uncompressed image to a compressed image the image texel
-- dimensions written to the compressed image will be the source extent
-- multiplied by the compressed texel block dimensions. In both cases the
-- number of bytes read and the number of bytes written will be identical.
--
-- Copying to or from block-compressed images is typically done in
-- multiples of the compressed texel block size. For this reason the
-- @extent@ /must/ be a multiple of the compressed texel block dimension.
-- There is one exception to this rule which is /required/ to handle
-- compressed images created with dimensions that are not a multiple of the
-- compressed texel block dimensions: if the @srcImage@ is compressed,
-- then:
--
-- -   If @extent.width@ is not a multiple of the compressed texel block
--     width, then (@extent.width@ + @srcOffset.x@) /must/ equal the image
--     subresource width.
--
-- -   If @extent.height@ is not a multiple of the compressed texel block
--     height, then (@extent.height@ + @srcOffset.y@) /must/ equal the
--     image subresource height.
--
-- -   If @extent.depth@ is not a multiple of the compressed texel block
--     depth, then (@extent.depth@ + @srcOffset.z@) /must/ equal the image
--     subresource depth.
--
-- Similarly, if the @dstImage@ is compressed, then:
--
-- -   If @extent.width@ is not a multiple of the compressed texel block
--     width, then (@extent.width@ + @dstOffset.x@) /must/ equal the image
--     subresource width.
--
-- -   If @extent.height@ is not a multiple of the compressed texel block
--     height, then (@extent.height@ + @dstOffset.y@) /must/ equal the
--     image subresource height.
--
-- -   If @extent.depth@ is not a multiple of the compressed texel block
--     depth, then (@extent.depth@ + @dstOffset.z@) /must/ equal the image
--     subresource depth.
--
-- This allows the last compressed texel block of the image in each
-- non-multiple dimension to be included as a source or destination of the
-- copy.
--
-- “@_422@” image formats that are not
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar>
-- are treated as having a 2×1 compressed texel block for the purposes of
-- these rules.
--
-- 'cmdCopyImage' /can/ be used to copy image data between multisample
-- images, but both images /must/ have the same number of samples.
--
-- == Valid Usage
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @srcImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @dstImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstImage@
--     /must/ not be an unprotected image
--
-- -   The union of all source regions, and the union of all destination
--     regions, specified by the elements of @pRegions@, /must/ not overlap
--     in memory
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @srcImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_SRC_BIT'
--
-- -   @srcImage@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
--     usage flag
--
-- -   If @srcImage@ is non-sparse then the image or /disjoint/ plane to be
--     copied /must/ be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @srcImageLayout@ /must/ specify the layout of the image subresources
--     of @srcImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @srcImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @dstImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT'
--
-- -   @dstImage@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstImage@ is non-sparse then the image or /disjoint/ plane that
--     is the destination of the copy /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstImageLayout@ /must/ specify the layout of the image subresources
--     of @dstImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @dstImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
--
-- -   If the 'Vulkan.Core10.Enums.Format.Format' of each of @srcImage@ and
--     @dstImage@ is not a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     the 'Vulkan.Core10.Enums.Format.Format' of each of @srcImage@ and
--     @dstImage@ /must/ be compatible, as defined
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies-images-format-compatibility above>
--
-- -   In a copy to or from a plane of a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image>,
--     the 'Vulkan.Core10.Enums.Format.Format' of the image and plane
--     /must/ be compatible according to
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes the description of compatible planes>
--     for the plane being copied
--
-- -   The sample count of @srcImage@ and @dstImage@ /must/ match
--
-- -   The @srcSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ was created
--
-- -   The @dstSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ was created
--
-- -   The @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of
--     each element of @pRegions@ /must/ be less than or equal to the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @srcImage@ was created
--
-- -   The @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of
--     each element of @pRegions@ /must/ be less than or equal to the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @dstImage@ was created
--
-- -   The @srcOffset@ and @extent@ members of each element of @pRegions@
--     /must/ respect the image transfer granularity requirements of
--     @commandBuffer@’s command pool’s queue family, as described in
--     'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties'
--
-- -   The @dstOffset@ and @extent@ members of each element of @pRegions@
--     /must/ respect the image transfer granularity requirements of
--     @commandBuffer@’s command pool’s queue family, as described in
--     'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties'
--
-- -   @dstImage@ and @srcImage@ /must/ not have been created with @flags@
--     containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT'
--
-- -   If neither @srcImage@ nor @dstImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>
--     then for each element of @pRegions@, @srcSubresource.aspectMask@ and
--     @dstSubresource.aspectMask@ /must/ match
--
-- -   If @srcImage@ has a 'Vulkan.Core10.Enums.Format.Format' with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion two planes>
--     then for each element of @pRegions@, @srcSubresource.aspectMask@
--     /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT'
--
-- -   If @srcImage@ has a 'Vulkan.Core10.Enums.Format.Format' with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion three planes>
--     then for each element of @pRegions@, @srcSubresource.aspectMask@
--     /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT',
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--
-- -   If @dstImage@ has a 'Vulkan.Core10.Enums.Format.Format' with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion two planes>
--     then for each element of @pRegions@, @dstSubresource.aspectMask@
--     /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT'
--
-- -   If @dstImage@ has a 'Vulkan.Core10.Enums.Format.Format' with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion three planes>
--     then for each element of @pRegions@, @dstSubresource.aspectMask@
--     /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT',
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--
-- -   If @srcImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>
--     and the @dstImage@ does not have a multi-planar image format, then
--     for each element of @pRegions@, @dstSubresource.aspectMask@ /must/
--     be 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'
--
-- -   If @dstImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>
--     and the @srcImage@ does not have a multi-planar image format, then
--     for each element of @pRegions@, @srcSubresource.aspectMask@ /must/
--     be 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element
--     of @pRegions@, @srcSubresource.baseArrayLayer@ /must/ be @0@ and and
--     @srcSubresource.layerCount@ /must/ be @1@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element
--     of @pRegions@, @dstSubresource.baseArrayLayer@ /must/ be @0@ and and
--     @dstSubresource.layerCount@ /must/ be @1@
--
-- -   For each element of @pRegions@, @srcSubresource.aspectMask@ /must/
--     specify aspects present in @srcImage@
--
-- -   For each element of @pRegions@, @dstSubresource.aspectMask@ /must/
--     specify aspects present in @dstImage@
--
-- -   For each element of @pRegions@, @srcOffset.x@ and (@extent.width@ +
--     @srcOffset.x@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the width of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   For each element of @pRegions@, @srcOffset.y@ and (@extent.height@ +
--     @srcOffset.y@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the height of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @srcOffset.y@ /must/ be @0@ and @extent.height@
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @srcOffset.z@ and (@extent.depth@ +
--     @srcOffset.z@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the depth of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @srcOffset.z@ /must/ be @0@ and @extent.depth@ /must/
--     be @1@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @dstOffset.z@ /must/ be @0@ and @extent.depth@ /must/
--     be @1@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @srcOffset.z@ /must/ be @0@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @dstOffset.z@ /must/ be @0@
--
-- -   If @srcImage@ and @dstImage@ are both of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @extent.depth@ /must/ be @1@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', and @dstImage@ is of
--     type 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each
--     element of @pRegions@, @extent.depth@ /must/ equal
--     @srcSubresource.layerCount@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', and @srcImage@ is of
--     type 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each
--     element of @pRegions@, @extent.depth@ /must/ equal
--     @dstSubresource.layerCount@
--
-- -   For each element of @pRegions@, @dstOffset.x@ and (@extent.width@ +
--     @dstOffset.x@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the width of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   For each element of @pRegions@, @dstOffset.y@ and (@extent.height@ +
--     @dstOffset.y@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the height of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @dstOffset.y@ /must/ be @0@ and @extent.height@
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @dstOffset.z@ and (@extent.depth@ +
--     @dstOffset.z@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the depth of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, all members of @srcOffset@
--     /must/ be a multiple of the corresponding dimensions of the
--     compressed texel block
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, @extent.width@ /must/ be a
--     multiple of the compressed texel block width or (@extent.width@ +
--     @srcOffset.x@) /must/ equal the width of the specified
--     @srcSubresource@ of @srcImage@
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, @extent.height@ /must/ be a
--     multiple of the compressed texel block height or (@extent.height@ +
--     @srcOffset.y@) /must/ equal the height of the specified
--     @srcSubresource@ of @srcImage@
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, @extent.depth@ /must/ be a
--     multiple of the compressed texel block depth or (@extent.depth@ +
--     @srcOffset.z@) /must/ equal the depth of the specified
--     @srcSubresource@ of @srcImage@
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, all members of @dstOffset@
--     /must/ be a multiple of the corresponding dimensions of the
--     compressed texel block
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, @extent.width@ /must/ be a
--     multiple of the compressed texel block width or (@extent.width@ +
--     @dstOffset.x@) /must/ equal the width of the specified
--     @dstSubresource@ of @dstImage@
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, @extent.height@ /must/ be a
--     multiple of the compressed texel block height or (@extent.height@ +
--     @dstOffset.y@) /must/ equal the height of the specified
--     @dstSubresource@ of @dstImage@
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     then for each element of @pRegions@, @extent.depth@ /must/ be a
--     multiple of the compressed texel block depth or (@extent.depth@ +
--     @dstOffset.z@) /must/ equal the depth of the specified
--     @dstSubresource@ of @dstImage@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @srcImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @dstImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @dstImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @pRegions@ /must/ be a valid pointer to an array of @regionCount@
--     valid 'ImageCopy' structures
--
-- -   @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 transfer, graphics, or compute
--     operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @regionCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @dstImage@, and @srcImage@ /must/ have been
--     created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Image',
-- 'ImageCopy', 'Vulkan.Core10.Enums.ImageLayout.ImageLayout'
cmdCopyImage :: forall io
              . (MonadIO io)
             => -- | @commandBuffer@ is the command buffer into which the command will be
                -- recorded.
                CommandBuffer
             -> -- | @srcImage@ is the source image.
                ("srcImage" ::: Image)
             -> -- | @srcImageLayout@ is the current layout of the source image subresource.
                ("srcImageLayout" ::: ImageLayout)
             -> -- | @dstImage@ is the destination image.
                ("dstImage" ::: Image)
             -> -- | @dstImageLayout@ is the current layout of the destination image
                -- subresource.
                ("dstImageLayout" ::: ImageLayout)
             -> -- | @pRegions@ is a pointer to an array of 'ImageCopy' structures specifying
                -- the regions to copy.
                ("regions" ::: Vector ImageCopy)
             -> io ()
cmdCopyImage :: CommandBuffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("regions" ::: Vector ImageCopy)
-> io ()
cmdCopyImage commandBuffer :: CommandBuffer
commandBuffer srcImage :: "srcImage" ::: Image
srcImage srcImageLayout :: "srcImageLayout" ::: ImageLayout
srcImageLayout dstImage :: "srcImage" ::: Image
dstImage dstImageLayout :: "srcImageLayout" ::: ImageLayout
dstImageLayout regions :: "regions" ::: Vector ImageCopy
regions = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyImagePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageCopy)
   -> IO ())
vkCmdCopyImagePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr ImageCopy)
      -> IO ())
pVkCmdCopyImage (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageCopy)
   -> IO ())
vkCmdCopyImagePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageCopy)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr ImageCopy)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageCopy)
   -> 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 vkCmdCopyImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyImage' :: Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageCopy)
-> IO ()
vkCmdCopyImage' = FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageCopy)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageCopy)
-> IO ()
mkVkCmdCopyImage FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageCopy)
   -> IO ())
vkCmdCopyImagePtr
  "pRegions" ::: Ptr ImageCopy
pPRegions <- ((("pRegions" ::: Ptr ImageCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr ImageCopy)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRegions" ::: Ptr ImageCopy) -> IO ()) -> IO ())
 -> ContT () IO ("pRegions" ::: Ptr ImageCopy))
-> ((("pRegions" ::: Ptr ImageCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr ImageCopy)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pRegions" ::: Ptr ImageCopy) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageCopy ((("regions" ::: Vector ImageCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length ("regions" ::: Vector ImageCopy
regions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 68) 4
  (Int -> ImageCopy -> ContT () IO ())
-> ("regions" ::: Vector ImageCopy) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageCopy
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRegions" ::: Ptr ImageCopy) -> ImageCopy -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRegions" ::: Ptr ImageCopy
pPRegions ("pRegions" ::: Ptr ImageCopy)
-> Int -> "pRegions" ::: Ptr ImageCopy
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (68 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageCopy) (ImageCopy
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("regions" ::: Vector ImageCopy
regions)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageCopy)
-> IO ()
vkCmdCopyImage' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("srcImage" ::: Image
srcImage) ("srcImageLayout" ::: ImageLayout
srcImageLayout) ("srcImage" ::: Image
dstImage) ("srcImageLayout" ::: ImageLayout
dstImageLayout) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("regions" ::: Vector ImageCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length (("regions" ::: Vector ImageCopy) -> Int)
-> ("regions" ::: Vector ImageCopy) -> Int
forall a b. (a -> b) -> a -> b
$ ("regions" ::: Vector ImageCopy
regions)) :: Word32)) ("pRegions" ::: Ptr ImageCopy
pPRegions)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBlitImage
  :: FunPtr (Ptr CommandBuffer_T -> Image -> ImageLayout -> Image -> ImageLayout -> Word32 -> Ptr ImageBlit -> Filter -> IO ()) -> Ptr CommandBuffer_T -> Image -> ImageLayout -> Image -> ImageLayout -> Word32 -> Ptr ImageBlit -> Filter -> IO ()

-- | vkCmdBlitImage - Copy regions of an image, potentially performing format
-- conversion,
--
-- = Description
--
-- 'cmdBlitImage' /must/ not be used for multisampled source or destination
-- images. Use 'cmdResolveImage' for this purpose.
--
-- As the sizes of the source and destination extents /can/ differ in any
-- dimension, texels in the source extent are scaled and filtered to the
-- destination extent. Scaling occurs via the following operations:
--
-- -   For each destination texel, the integer coordinate of that texel is
--     converted to an unnormalized texture coordinate, using the effective
--     inverse of the equations described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-unnormalized-to-integer unnormalized to integer conversion>:
--
--     -   ubase = i + ½
--
--     -   vbase = j + ½
--
--     -   wbase = k + ½
--
-- -   These base coordinates are then offset by the first destination
--     offset:
--
--     -   uoffset = ubase - xdst0
--
--     -   voffset = vbase - ydst0
--
--     -   woffset = wbase - zdst0
--
--     -   aoffset = a - @baseArrayCount@dst
--
-- -   The scale is determined from the source and destination regions, and
--     applied to the offset coordinates:
--
--     -   scaleu = (xsrc1 - xsrc0) \/ (xdst1 - xdst0)
--
--     -   scalev = (ysrc1 - ysrc0) \/ (ydst1 - ydst0)
--
--     -   scalew = (zsrc1 - zsrc0) \/ (zdst1 - zdst0)
--
--     -   uscaled = uoffset × scaleu
--
--     -   vscaled = voffset × scalev
--
--     -   wscaled = woffset × scalew
--
-- -   Finally the source offset is added to the scaled coordinates, to
--     determine the final unnormalized coordinates used to sample from
--     @srcImage@:
--
--     -   u = uscaled + xsrc0
--
--     -   v = vscaled + ysrc0
--
--     -   w = wscaled + zsrc0
--
--     -   q = @mipLevel@
--
--     -   a = aoffset + @baseArrayCount@src
--
-- These coordinates are used to sample from the source image, as described
-- in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures Image Operations chapter>,
-- with the filter mode equal to that of @filter@, a mipmap mode of
-- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_NEAREST' and
-- an address mode of
-- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE'.
-- Implementations /must/ clamp at the edge of the source image, and /may/
-- additionally clamp to the edge of the source region.
--
-- Note
--
-- Due to allowable rounding errors in the generation of the source texture
-- coordinates, it is not always possible to guarantee exactly which source
-- texels will be sampled for a given blit. As rounding errors are
-- implementation dependent, the exact results of a blitting operation are
-- also implementation dependent.
--
-- Blits are done layer by layer starting with the @baseArrayLayer@ member
-- of @srcSubresource@ for the source and @dstSubresource@ for the
-- destination. @layerCount@ layers are blitted to the destination image.
--
-- When blitting 3D textures, slices in the destination region bounded by
-- @dstOffsets@[0].z and @dstOffsets@[1].z are sampled from slices in the
-- source region bounded by @srcOffsets@[0].z and @srcOffsets@[1].z. If the
-- @filter@ parameter is 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' then
-- the value sampled from the source image is taken by doing linear
-- filtering using the interpolated __z__ coordinate represented by __w__
-- in the previous equations. If the @filter@ parameter is
-- 'Vulkan.Core10.Enums.Filter.FILTER_NEAREST' then the value sampled from
-- the source image is taken from the single nearest slice, with an
-- implementation-dependent arithmetic rounding mode.
--
-- The following filtering and conversion rules apply:
--
-- -   Integer formats /can/ only be converted to other integer formats
--     with the same signedness.
--
-- -   No format conversion is supported between depth\/stencil images. The
--     formats /must/ match.
--
-- -   Format conversions on unorm, snorm, unscaled and packed float
--     formats of the copied aspect of the image are performed by first
--     converting the pixels to float values.
--
-- -   For sRGB source formats, nonlinear RGB values are converted to
--     linear representation prior to filtering.
--
-- -   After filtering, the float values are first clamped and then cast to
--     the destination image format. In case of sRGB destination format,
--     linear RGB values are converted to nonlinear representation before
--     writing the pixel to the image.
--
-- Signed and unsigned integers are converted by first clamping to the
-- representable range of the destination format, then casting the value.
--
-- == Valid Usage
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @srcImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @dstImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstImage@
--     /must/ not be an unprotected image
--
-- -   The source region specified by each element of @pRegions@ /must/ be
--     a region that is contained within @srcImage@
--
-- -   The destination region specified by each element of @pRegions@
--     /must/ be a region that is contained within @dstImage@
--
-- -   The union of all destination regions, specified by the elements of
--     @pRegions@, /must/ not overlap in memory with any texel that /may/
--     be sampled during the blit operation
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @srcImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_SRC_BIT'
--
-- -   @srcImage@ /must/ not use a format listed in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion ???>
--
-- -   @srcImage@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
--     usage flag
--
-- -   If @srcImage@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @srcImageLayout@ /must/ specify the layout of the image subresources
--     of @srcImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @srcImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL'
--     or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL'
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @dstImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_DST_BIT'
--
-- -   @dstImage@ /must/ not use a format listed in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion ???>
--
-- -   @dstImage@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstImage@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstImageLayout@ /must/ specify the layout of the image subresources
--     of @dstImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @dstImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'
--     or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL'
--
-- -   If either of @srcImage@ or @dstImage@ was created with a signed
--     integer 'Vulkan.Core10.Enums.Format.Format', the other /must/ also
--     have been created with a signed integer
--     'Vulkan.Core10.Enums.Format.Format'
--
-- -   If either of @srcImage@ or @dstImage@ was created with an unsigned
--     integer 'Vulkan.Core10.Enums.Format.Format', the other /must/ also
--     have been created with an unsigned integer
--     'Vulkan.Core10.Enums.Format.Format'
--
-- -   If either of @srcImage@ or @dstImage@ was created with a
--     depth\/stencil format, the other /must/ have exactly the same format
--
-- -   If @srcImage@ was created with a depth\/stencil format, @filter@
--     /must/ be 'Vulkan.Core10.Enums.Filter.FILTER_NEAREST'
--
-- -   @srcImage@ /must/ have been created with a @samples@ value of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   @dstImage@ /must/ have been created with a @samples@ value of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   If @filter@ is 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @srcImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
--
-- -   If @filter@ is
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @srcImage@ /must/ contain
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT'
--
-- -   If @filter@ is
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT', @srcImage@
--     /must/ be of type 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D'
--
-- -   The @srcSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ was created
--
-- -   The @dstSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ was created
--
-- -   The @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of
--     each element of @pRegions@ /must/ be less than or equal to the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @srcImage@ was created
--
-- -   The @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of
--     each element of @pRegions@ /must/ be less than or equal to the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @dstImage@ was created
--
-- -   @dstImage@ and @srcImage@ /must/ not have been created with @flags@
--     containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT'
--
-- -   If either @srcImage@ or @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element
--     of @pRegions@, @srcSubresource.baseArrayLayer@ and
--     @dstSubresource.baseArrayLayer@ /must/ each be @0@, and
--     @srcSubresource.layerCount@ and @dstSubresource.layerCount@ /must/
--     each be @1@.
--
-- -   For each element of @pRegions@, @srcSubresource.aspectMask@ /must/
--     specify aspects present in @srcImage@
--
-- -   For each element of @pRegions@, @dstSubresource.aspectMask@ /must/
--     specify aspects present in @dstImage@
--
-- -   For each element of @pRegions@, @srcOffset@[0].x and
--     @srcOffset@[1].x /must/ both be greater than or equal to @0@ and
--     less than or equal to the width of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   For each element of @pRegions@, @srcOffset@[0].y and
--     @srcOffset@[1].y /must/ both be greater than or equal to @0@ and
--     less than or equal to the height of the specified @srcSubresource@
--     of @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @srcOffset@[0].y /must/ be @0@ and @srcOffset@[1].y
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @srcOffset@[0].z and
--     @srcOffset@[1].z /must/ both be greater than or equal to @0@ and
--     less than or equal to the depth of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' or
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @srcOffset@[0].z /must/ be @0@ and @srcOffset@[1].z
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @dstOffset@[0].x and
--     @dstOffset@[1].x /must/ both be greater than or equal to @0@ and
--     less than or equal to the width of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   For each element of @pRegions@, @dstOffset@[0].y and
--     @dstOffset@[1].y /must/ both be greater than or equal to @0@ and
--     less than or equal to the height of the specified @dstSubresource@
--     of @dstImage@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @dstOffset@[0].y /must/ be @0@ and @dstOffset@[1].y
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @dstOffset@[0].z and
--     @dstOffset@[1].z /must/ both be greater than or equal to @0@ and
--     less than or equal to the depth of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' or
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @dstOffset@[0].z /must/ be @0@ and @dstOffset@[1].z
--     /must/ be @1@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @srcImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @dstImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @dstImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @pRegions@ /must/ be a valid pointer to an array of @regionCount@
--     valid 'ImageBlit' structures
--
-- -   @filter@ /must/ be a valid 'Vulkan.Core10.Enums.Filter.Filter' value
--
-- -   @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 operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @regionCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @dstImage@, and @srcImage@ /must/ have been
--     created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.Filter.Filter', 'Vulkan.Core10.Handles.Image',
-- 'ImageBlit', 'Vulkan.Core10.Enums.ImageLayout.ImageLayout'
cmdBlitImage :: forall io
              . (MonadIO io)
             => -- | @commandBuffer@ is the command buffer into which the command will be
                -- recorded.
                CommandBuffer
             -> -- | @srcImage@ is the source image.
                ("srcImage" ::: Image)
             -> -- | @srcImageLayout@ is the layout of the source image subresources for the
                -- blit.
                ("srcImageLayout" ::: ImageLayout)
             -> -- | @dstImage@ is the destination image.
                ("dstImage" ::: Image)
             -> -- | @dstImageLayout@ is the layout of the destination image subresources for
                -- the blit.
                ("dstImageLayout" ::: ImageLayout)
             -> -- | @pRegions@ is a pointer to an array of 'ImageBlit' structures specifying
                -- the regions to blit.
                ("regions" ::: Vector ImageBlit)
             -> -- | @filter@ is a 'Vulkan.Core10.Enums.Filter.Filter' specifying the filter
                -- to apply if the blits require scaling.
                Filter
             -> io ()
cmdBlitImage :: CommandBuffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("regions" ::: Vector ImageBlit)
-> Filter
-> io ()
cmdBlitImage commandBuffer :: CommandBuffer
commandBuffer srcImage :: "srcImage" ::: Image
srcImage srcImageLayout :: "srcImageLayout" ::: ImageLayout
srcImageLayout dstImage :: "srcImage" ::: Image
dstImage dstImageLayout :: "srcImageLayout" ::: ImageLayout
dstImageLayout regions :: "regions" ::: Vector ImageBlit
regions filter' :: Filter
filter' = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdBlitImagePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageBlit)
   -> Filter
   -> IO ())
vkCmdBlitImagePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr ImageBlit)
      -> Filter
      -> IO ())
pVkCmdBlitImage (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageBlit)
   -> Filter
   -> IO ())
vkCmdBlitImagePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageBlit)
   -> Filter
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr ImageBlit)
      -> Filter
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageBlit)
   -> Filter
   -> 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 vkCmdBlitImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBlitImage' :: Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageBlit)
-> Filter
-> IO ()
vkCmdBlitImage' = FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageBlit)
   -> Filter
   -> IO ())
-> Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageBlit)
-> Filter
-> IO ()
mkVkCmdBlitImage FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageBlit)
   -> Filter
   -> IO ())
vkCmdBlitImagePtr
  "pRegions" ::: Ptr ImageBlit
pPRegions <- ((("pRegions" ::: Ptr ImageBlit) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr ImageBlit)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRegions" ::: Ptr ImageBlit) -> IO ()) -> IO ())
 -> ContT () IO ("pRegions" ::: Ptr ImageBlit))
-> ((("pRegions" ::: Ptr ImageBlit) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr ImageBlit)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pRegions" ::: Ptr ImageBlit) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageBlit ((("regions" ::: Vector ImageBlit) -> Int
forall a. Vector a -> Int
Data.Vector.length ("regions" ::: Vector ImageBlit
regions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 80) 4
  (Int -> ImageBlit -> ContT () IO ())
-> ("regions" ::: Vector ImageBlit) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageBlit
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRegions" ::: Ptr ImageBlit) -> ImageBlit -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRegions" ::: Ptr ImageBlit
pPRegions ("pRegions" ::: Ptr ImageBlit)
-> Int -> "pRegions" ::: Ptr ImageBlit
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageBlit) (ImageBlit
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("regions" ::: Vector ImageBlit
regions)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageBlit)
-> Filter
-> IO ()
vkCmdBlitImage' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("srcImage" ::: Image
srcImage) ("srcImageLayout" ::: ImageLayout
srcImageLayout) ("srcImage" ::: Image
dstImage) ("srcImageLayout" ::: ImageLayout
dstImageLayout) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("regions" ::: Vector ImageBlit) -> Int
forall a. Vector a -> Int
Data.Vector.length (("regions" ::: Vector ImageBlit) -> Int)
-> ("regions" ::: Vector ImageBlit) -> Int
forall a b. (a -> b) -> a -> b
$ ("regions" ::: Vector ImageBlit
regions)) :: Word32)) ("pRegions" ::: Ptr ImageBlit
pPRegions) (Filter
filter')
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdCopyBufferToImage
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> Image -> ImageLayout -> Word32 -> Ptr BufferImageCopy -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> Image -> ImageLayout -> Word32 -> Ptr BufferImageCopy -> IO ()

-- | vkCmdCopyBufferToImage - Copy data from a buffer into an image
--
-- = Description
--
-- Each region in @pRegions@ is copied from the specified region of the
-- source buffer to the specified region of the destination image.
--
-- If the format of @dstImage@ is a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>,
-- regions of each plane to be a target of a copy /must/ be specified
-- separately using the @pRegions@ member of the 'BufferImageCopy'
-- structure. In this case, the @aspectMask@ of @imageSubresource@ /must/
-- be 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', or
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'. For
-- the purposes of 'cmdCopyBufferToImage', each plane of a multi-planar
-- image is treated as having the format listed in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes>
-- for the plane identified by the @aspectMask@ of the corresponding
-- subresource. This applies both to 'Vulkan.Core10.Enums.Format.Format'
-- and to coordinates used in the copy, which correspond to texels in the
-- /plane/ rather than how these texels map to coordinates in the image as
-- a whole.
--
-- == Valid Usage
--
-- -   If @commandBuffer@ is an unprotected command buffer, then
--     @srcBuffer@ /must/ not be a protected buffer
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @dstImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstImage@
--     /must/ not be an unprotected image
--
-- -   @srcBuffer@ /must/ be large enough to contain all buffer locations
--     that are accessed according to
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies-buffers-images-addressing Buffer and Image Addressing>,
--     for each element of @pRegions@
--
-- -   The image region specified by each element of @pRegions@ /must/ be a
--     region that is contained within @dstImage@ if the @dstImage@’s
--     'Vulkan.Core10.Enums.Format.Format' is not a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     and /must/ be a region that is contained within the plane being
--     copied to if the @dstImage@’s 'Vulkan.Core10.Enums.Format.Format' is
--     a multi-planar format
--
-- -   The union of all source regions, and the union of all destination
--     regions, specified by the elements of @pRegions@, /must/ not overlap
--     in memory
--
-- -   @srcBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_SRC_BIT'
--     usage flag
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @dstImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT'
--
-- -   If @srcBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstImage@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstImage@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstImage@ /must/ have a sample count equal to
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   @dstImageLayout@ /must/ specify the layout of the image subresources
--     of @dstImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @dstImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
--
-- -   The @imageSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ was created
--
-- -   The @imageSubresource.baseArrayLayer@ +
--     @imageSubresource.layerCount@ of each element of @pRegions@ /must/
--     be less than or equal to the @arrayLayers@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ was created
--
-- -   The @imageOffset@ and @imageExtent@ members of each element of
--     @pRegions@ /must/ respect the image transfer granularity
--     requirements of @commandBuffer@’s command pool’s queue family, as
--     described in
--     'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties'
--
-- -   @dstImage@ /must/ not have been created with @flags@ containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT'
--
-- -   If the queue family used to create the
--     'Vulkan.Core10.Handles.CommandPool' which @commandBuffer@ was
--     allocated from does not support
--     'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
--     'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT', the
--     @bufferOffset@ member of any element of @pRegions@ /must/ be a
--     multiple of @4@
--
-- -   If @dstImage@ has a depth\/stencil format, the @bufferOffset@ member
--     of any element of @pRegions@ /must/ be a multiple of @4@
--
-- -   If the queue family used to create the
--     'Vulkan.Core10.Handles.CommandPool' which @commandBuffer@ was
--     allocated from does not support
--     'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT', for each
--     element of @pRegions@, the @aspectMask@ member of @imageSubresource@
--     /must/ not be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'.
--
-- -   If @dstImage@ does not have either a depth\/stencil or a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     then for each element of @pRegions@, @bufferOffset@ /must/ be a
--     multiple of the format’s texel block size
--
-- -   If @dstImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     then for each element of @pRegions@, @bufferOffset@ /must/ be a
--     multiple of the element size of the compatible format for the format
--     and the @aspectMask@ of the @imageSubresource@ as defined in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes ???>
--
-- -   For each element of @pRegions@, @imageOffset.x@ and
--     (@imageExtent.width@ + @imageOffset.x@) /must/ both be greater than
--     or equal to @0@ and less than or equal to the width of the specified
--     @imageSubresource@ of @dstImage@ where this refers to the width of
--     the /plane/ of the image involved in the copy in the case of a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>
--
-- -   For each element of @pRegions@, @imageOffset.y@ and
--     (imageExtent.height + @imageOffset.y@) /must/ both be greater than
--     or equal to @0@ and less than or equal to the height of the
--     specified @imageSubresource@ of @dstImage@ where this refers to the
--     height of the /plane/ of the image involved in the copy in the case
--     of a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @imageOffset.y@ /must/ be @0@ and
--     @imageExtent.height@ /must/ be @1@
--
-- -   For each element of @pRegions@, @imageOffset.z@ and
--     (imageExtent.depth + @imageOffset.z@) /must/ both be greater than or
--     equal to @0@ and less than or equal to the depth of the specified
--     @imageSubresource@ of @dstImage@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' or
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @imageOffset.z@ /must/ be @0@ and @imageExtent.depth@
--     /must/ be @1@
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @bufferRowLength@ /must/ be a
--     multiple of the compressed texel block width
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @bufferImageHeight@ /must/ be a
--     multiple of the compressed texel block height
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, all members of @imageOffset@ /must/
--     be a multiple of the corresponding dimensions of the compressed
--     texel block
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @bufferOffset@ /must/ be a multiple
--     of the compressed texel block size in bytes
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @imageExtent.width@ /must/ be a
--     multiple of the compressed texel block width or (@imageExtent.width@
--     + @imageOffset.x@) /must/ equal the width of the specified
--     @imageSubresource@ of @dstImage@
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @imageExtent.height@ /must/ be a
--     multiple of the compressed texel block height or
--     (@imageExtent.height@ + @imageOffset.y@) /must/ equal the height of
--     the specified @imageSubresource@ of @dstImage@
--
-- -   If @dstImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @imageExtent.depth@ /must/ be a
--     multiple of the compressed texel block depth or (@imageExtent.depth@
--     + @imageOffset.z@) /must/ equal the depth of the specified
--     @imageSubresource@ of @dstImage@
--
-- -   For each element of @pRegions@, @imageSubresource.aspectMask@ /must/
--     specify aspects present in @dstImage@
--
-- -   If @dstImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     then for each element of @pRegions@, @imageSubresource.aspectMask@
--     /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT',
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--     (with
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--     valid only for image formats with three planes)
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', for each element of
--     @pRegions@, @imageSubresource.baseArrayLayer@ /must/ be @0@ and
--     @imageSubresource.layerCount@ /must/ be @1@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @dstImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @dstImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @pRegions@ /must/ be a valid pointer to an array of @regionCount@
--     valid 'BufferImageCopy' structures
--
-- -   @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 transfer, graphics, or compute
--     operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @regionCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @dstImage@, and @srcBuffer@ /must/ have
--     been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'BufferImageCopy',
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout'
cmdCopyBufferToImage :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command will be
                        -- recorded.
                        CommandBuffer
                     -> -- | @srcBuffer@ is the source buffer.
                        ("srcBuffer" ::: Buffer)
                     -> -- | @dstImage@ is the destination image.
                        ("dstImage" ::: Image)
                     -> -- | @dstImageLayout@ is the layout of the destination image subresources for
                        -- the copy.
                        ("dstImageLayout" ::: ImageLayout)
                     -> -- | @pRegions@ is a pointer to an array of 'BufferImageCopy' structures
                        -- specifying the regions to copy.
                        ("regions" ::: Vector BufferImageCopy)
                     -> io ()
cmdCopyBufferToImage :: CommandBuffer
-> Buffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("regions" ::: Vector BufferImageCopy)
-> io ()
cmdCopyBufferToImage commandBuffer :: CommandBuffer
commandBuffer srcBuffer :: Buffer
srcBuffer dstImage :: "srcImage" ::: Image
dstImage dstImageLayout :: "srcImageLayout" ::: ImageLayout
dstImageLayout regions :: "regions" ::: Vector BufferImageCopy
regions = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyBufferToImagePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
vkCmdCopyBufferToImagePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr BufferImageCopy)
      -> IO ())
pVkCmdCopyBufferToImage (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
vkCmdCopyBufferToImagePtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr BufferImageCopy)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> 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 vkCmdCopyBufferToImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyBufferToImage' :: Ptr CommandBuffer_T
-> Buffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferImageCopy)
-> IO ()
vkCmdCopyBufferToImage' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferImageCopy)
-> IO ()
mkVkCmdCopyBufferToImage FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
vkCmdCopyBufferToImagePtr
  "pRegions" ::: Ptr BufferImageCopy
pPRegions <- ((("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr BufferImageCopy)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ())
 -> ContT () IO ("pRegions" ::: Ptr BufferImageCopy))
-> ((("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr BufferImageCopy)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @BufferImageCopy ((("regions" ::: Vector BufferImageCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length ("regions" ::: Vector BufferImageCopy
regions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
  (Int -> BufferImageCopy -> ContT () IO ())
-> ("regions" ::: Vector BufferImageCopy) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: BufferImageCopy
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRegions" ::: Ptr BufferImageCopy)
-> BufferImageCopy -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRegions" ::: Ptr BufferImageCopy
pPRegions ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pRegions" ::: Ptr BufferImageCopy
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr BufferImageCopy) (BufferImageCopy
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("regions" ::: Vector BufferImageCopy
regions)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> Buffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferImageCopy)
-> IO ()
vkCmdCopyBufferToImage' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
srcBuffer) ("srcImage" ::: Image
dstImage) ("srcImageLayout" ::: ImageLayout
dstImageLayout) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("regions" ::: Vector BufferImageCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length (("regions" ::: Vector BufferImageCopy) -> Int)
-> ("regions" ::: Vector BufferImageCopy) -> Int
forall a b. (a -> b) -> a -> b
$ ("regions" ::: Vector BufferImageCopy
regions)) :: Word32)) ("pRegions" ::: Ptr BufferImageCopy
pPRegions)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdCopyImageToBuffer
  :: FunPtr (Ptr CommandBuffer_T -> Image -> ImageLayout -> Buffer -> Word32 -> Ptr BufferImageCopy -> IO ()) -> Ptr CommandBuffer_T -> Image -> ImageLayout -> Buffer -> Word32 -> Ptr BufferImageCopy -> IO ()

-- | vkCmdCopyImageToBuffer - Copy image data into a buffer
--
-- = Description
--
-- Each region in @pRegions@ is copied from the specified region of the
-- source image to the specified region of the destination buffer.
--
-- If the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ is a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>,
-- regions of each plane to be a source of a copy /must/ be specified
-- separately using the @pRegions@ member of the 'BufferImageCopy'
-- structure. In this case, the @aspectMask@ of @imageSubresource@ /must/
-- be 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', or
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'. For
-- the purposes of 'cmdCopyBufferToImage', each plane of a multi-planar
-- image is treated as having the format listed in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes>
-- for the plane identified by the @aspectMask@ of the corresponding
-- subresource. This applies both to 'Vulkan.Core10.Enums.Format.Format'
-- and to coordinates used in the copy, which correspond to texels in the
-- /plane/ rather than how these texels map to coordinates in the image as
-- a whole.
--
-- == Valid Usage
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @srcImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is an unprotected command buffer, then
--     @dstBuffer@ /must/ not be a protected buffer
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstBuffer@
--     /must/ not be an unprotected buffer
--
-- -   @dstBuffer@ /must/ be large enough to contain all buffer locations
--     that are accessed according to
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies-buffers-images-addressing Buffer and Image Addressing>,
--     for each element of @pRegions@
--
-- -   The image region specified by each element of @pRegions@ /must/ be a
--     region that is contained within @srcImage@ if the @srcImage@’s
--     'Vulkan.Core10.Enums.Format.Format' is not a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     and /must/ be a region that is contained within the plane being
--     copied if the @srcImage@’s 'Vulkan.Core10.Enums.Format.Format' is a
--     multi-planar format
--
-- -   The union of all source regions, and the union of all destination
--     regions, specified by the elements of @pRegions@, /must/ not overlap
--     in memory
--
-- -   @srcImage@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
--     usage flag
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @srcImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_SRC_BIT'
--
-- -   If @srcImage@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @srcImage@ /must/ have a sample count equal to
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   @srcImageLayout@ /must/ specify the layout of the image subresources
--     of @srcImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @srcImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
--
-- -   The @imageSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ was created
--
-- -   The @imageSubresource.baseArrayLayer@ +
--     @imageSubresource.layerCount@ of each element of @pRegions@ /must/
--     be less than or equal to the @arrayLayers@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ was created
--
-- -   The @imageOffset@ and @imageExtent@ members of each element of
--     @pRegions@ /must/ respect the image transfer granularity
--     requirements of @commandBuffer@’s command pool’s queue family, as
--     described in
--     'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties'
--
-- -   @srcImage@ /must/ not have been created with @flags@ containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT'
--
-- -   If the queue family used to create the
--     'Vulkan.Core10.Handles.CommandPool' which @commandBuffer@ was
--     allocated from does not support
--     'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
--     'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT', the
--     @bufferOffset@ member of any element of @pRegions@ /must/ be a
--     multiple of @4@
--
-- -   If @srcImage@ has a depth\/stencil format, the @bufferOffset@ member
--     of any element of @pRegions@ /must/ be a multiple of @4@
--
-- -   If @srcImage@ does not have either a depth\/stencil or a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     then for each element of @pRegions@, @bufferOffset@ /must/ be a
--     multiple of the format’s texel block size
--
-- -   If @srcImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     then for each element of @pRegions@, @bufferOffset@ /must/ be a
--     multiple of the element size of the compatible format for the format
--     and the @aspectMask@ of the @imageSubresource@ as defined in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes ???>
--
-- -   For each element of @pRegions@, @imageOffset.x@ and
--     (@imageExtent.width@ + @imageOffset.x@) /must/ both be greater than
--     or equal to @0@ and less than or equal to the width of the specified
--     @imageSubresource@ of @srcImage@ where this refers to the width of
--     the /plane/ of the image involved in the copy in the case of a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>
--
-- -   For each element of @pRegions@, @imageOffset.y@ and
--     (imageExtent.height + @imageOffset.y@) /must/ both be greater than
--     or equal to @0@ and less than or equal to the height of the
--     specified @imageSubresource@ of @srcImage@ where this refers to the
--     height of the /plane/ of the image involved in the copy in the case
--     of a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @imageOffset.y@ /must/ be @0@ and
--     @imageExtent.height@ /must/ be @1@
--
-- -   For each element of @pRegions@, @imageOffset.z@ and
--     (imageExtent.depth + @imageOffset.z@) /must/ both be greater than or
--     equal to @0@ and less than or equal to the depth of the specified
--     @imageSubresource@ of @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' or
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @imageOffset.z@ /must/ be @0@ and @imageExtent.depth@
--     /must/ be @1@
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @bufferRowLength@ /must/ be a
--     multiple of the compressed texel block width
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @bufferImageHeight@ /must/ be a
--     multiple of the compressed texel block height
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, all members of @imageOffset@ /must/
--     be a multiple of the corresponding dimensions of the compressed
--     texel block
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @bufferOffset@ /must/ be a multiple
--     of the compressed texel block size in bytes
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @imageExtent.width@ /must/ be a
--     multiple of the compressed texel block width or (@imageExtent.width@
--     + @imageOffset.x@) /must/ equal the width of the specified
--     @imageSubresource@ of @srcImage@
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @imageExtent.height@ /must/ be a
--     multiple of the compressed texel block height or
--     (@imageExtent.height@ + @imageOffset.y@) /must/ equal the height of
--     the specified @imageSubresource@ of @srcImage@
--
-- -   If @srcImage@ is a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#blocked-image blocked image>,
--     for each element of @pRegions@, @imageExtent.depth@ /must/ be a
--     multiple of the compressed texel block depth or (@imageExtent.depth@
--     + @imageOffset.z@) /must/ equal the depth of the specified
--     @imageSubresource@ of @srcImage@
--
-- -   For each element of @pRegions@, @imageSubresource.aspectMask@ /must/
--     specify aspects present in @srcImage@
--
-- -   If @srcImage@ has a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>,
--     then for each element of @pRegions@, @imageSubresource.aspectMask@
--     /must/ be
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT',
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--     (with
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--     valid only for image formats with three planes)
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', for each element of
--     @pRegions@, @imageSubresource.baseArrayLayer@ /must/ be @0@ and
--     @imageSubresource.layerCount@ /must/ be @1@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @srcImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @dstBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @pRegions@ /must/ be a valid pointer to an array of @regionCount@
--     valid 'BufferImageCopy' structures
--
-- -   @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 transfer, graphics, or compute
--     operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @regionCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @dstBuffer@, and @srcImage@ /must/ have
--     been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'BufferImageCopy',
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout'
cmdCopyImageToBuffer :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command will be
                        -- recorded.
                        CommandBuffer
                     -> -- | @srcImage@ is the source image.
                        ("srcImage" ::: Image)
                     -> -- | @srcImageLayout@ is the layout of the source image subresources for the
                        -- copy.
                        ("srcImageLayout" ::: ImageLayout)
                     -> -- | @dstBuffer@ is the destination buffer.
                        ("dstBuffer" ::: Buffer)
                     -> -- | @pRegions@ is a pointer to an array of 'BufferImageCopy' structures
                        -- specifying the regions to copy.
                        ("regions" ::: Vector BufferImageCopy)
                     -> io ()
cmdCopyImageToBuffer :: CommandBuffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> Buffer
-> ("regions" ::: Vector BufferImageCopy)
-> io ()
cmdCopyImageToBuffer commandBuffer :: CommandBuffer
commandBuffer srcImage :: "srcImage" ::: Image
srcImage srcImageLayout :: "srcImageLayout" ::: ImageLayout
srcImageLayout dstBuffer :: Buffer
dstBuffer regions :: "regions" ::: Vector BufferImageCopy
regions = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyImageToBufferPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
vkCmdCopyImageToBufferPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> Buffer
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr BufferImageCopy)
      -> IO ())
pVkCmdCopyImageToBuffer (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
vkCmdCopyImageToBufferPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> Buffer
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr BufferImageCopy)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> 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 vkCmdCopyImageToBuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyImageToBuffer' :: Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> Buffer
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferImageCopy)
-> IO ()
vkCmdCopyImageToBuffer' = FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> Buffer
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferImageCopy)
-> IO ()
mkVkCmdCopyImageToBuffer FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> Buffer
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr BufferImageCopy)
   -> IO ())
vkCmdCopyImageToBufferPtr
  "pRegions" ::: Ptr BufferImageCopy
pPRegions <- ((("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr BufferImageCopy)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ())
 -> ContT () IO ("pRegions" ::: Ptr BufferImageCopy))
-> ((("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr BufferImageCopy)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pRegions" ::: Ptr BufferImageCopy) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @BufferImageCopy ((("regions" ::: Vector BufferImageCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length ("regions" ::: Vector BufferImageCopy
regions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
  (Int -> BufferImageCopy -> ContT () IO ())
-> ("regions" ::: Vector BufferImageCopy) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: BufferImageCopy
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRegions" ::: Ptr BufferImageCopy)
-> BufferImageCopy -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRegions" ::: Ptr BufferImageCopy
pPRegions ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pRegions" ::: Ptr BufferImageCopy
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr BufferImageCopy) (BufferImageCopy
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("regions" ::: Vector BufferImageCopy
regions)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> Buffer
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr BufferImageCopy)
-> IO ()
vkCmdCopyImageToBuffer' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("srcImage" ::: Image
srcImage) ("srcImageLayout" ::: ImageLayout
srcImageLayout) (Buffer
dstBuffer) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("regions" ::: Vector BufferImageCopy) -> Int
forall a. Vector a -> Int
Data.Vector.length (("regions" ::: Vector BufferImageCopy) -> Int)
-> ("regions" ::: Vector BufferImageCopy) -> Int
forall a b. (a -> b) -> a -> b
$ ("regions" ::: Vector BufferImageCopy
regions)) :: Word32)) ("pRegions" ::: Ptr BufferImageCopy
pPRegions)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdUpdateBuffer - Update a buffer’s contents from host memory
--
-- = Description
--
-- @dataSize@ /must/ be less than or equal to 65536 bytes. For larger
-- updates, applications /can/ use buffer to buffer
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies-buffers copies>.
--
-- Note
--
-- Buffer updates performed with 'cmdUpdateBuffer' first copy the data into
-- command buffer memory when the command is recorded (which requires
-- additional storage and may incur an additional allocation), and then
-- copy the data from the command buffer into @dstBuffer@ when the command
-- is executed on a device.
--
-- The additional cost of this functionality compared to
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies-buffers buffer to buffer copies>
-- means it is only recommended for very small amounts of data, and is why
-- it is limited to only 65536 bytes.
--
-- Applications /can/ work around this by issuing multiple
-- 'cmdUpdateBuffer' commands to different ranges of the same buffer, but
-- it is strongly recommended that they /should/ not.
--
-- The source data is copied from the user pointer to the command buffer
-- when the command is called.
--
-- 'cmdUpdateBuffer' is only allowed outside of a render pass. This command
-- is treated as “transfer” operation, for the purposes of synchronization
-- barriers. The
-- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
-- /must/ be specified in @usage@ of
-- 'Vulkan.Core10.Buffer.BufferCreateInfo' in order for the buffer to be
-- compatible with 'cmdUpdateBuffer'.
--
-- == Valid Usage
--
-- -   @dstOffset@ /must/ be less than the size of @dstBuffer@
--
-- -   @dataSize@ /must/ be less than or equal to the size of @dstBuffer@
--     minus @dstOffset@
--
-- -   @dstBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstOffset@ /must/ be a multiple of @4@
--
-- -   @dataSize@ /must/ be less than or equal to @65536@
--
-- -   @dataSize@ /must/ be a multiple of @4@
--
-- -   If @commandBuffer@ is an unprotected command buffer, then
--     @dstBuffer@ /must/ not be a protected buffer
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstBuffer@
--     /must/ not be an unprotected buffer
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @dstBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @pData@ /must/ be a valid pointer to an array of @dataSize@ bytes
--
-- -   @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 transfer, graphics, or compute
--     operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @dataSize@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and @dstBuffer@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdUpdateBuffer :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command will be
                   -- recorded.
                   CommandBuffer
                -> -- | @dstBuffer@ is a handle to the buffer to be updated.
                   ("dstBuffer" ::: Buffer)
                -> -- | @dstOffset@ is the byte offset into the buffer to start updating, and
                   -- /must/ be a multiple of 4.
                   ("dstOffset" ::: DeviceSize)
                -> -- | @dataSize@ is the number of bytes to update, and /must/ be a multiple of
                   -- 4.
                   ("dataSize" ::: DeviceSize)
                -> -- | @pData@ is a pointer to the source data for the buffer update, and
                   -- /must/ be at least @dataSize@ bytes in size.
                   ("data" ::: Ptr ())
                -> io ()
cmdUpdateBuffer :: CommandBuffer
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("data" ::: Ptr ())
-> io ()
cmdUpdateBuffer commandBuffer :: CommandBuffer
commandBuffer dstBuffer :: Buffer
dstBuffer dstOffset :: "offset" ::: DeviceSize
dstOffset dataSize :: "offset" ::: DeviceSize
dataSize data' :: "data" ::: Ptr ()
data' = 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 vkCmdUpdateBufferPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdUpdateBufferPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("offset" ::: DeviceSize)
      -> ("data" ::: Ptr ())
      -> IO ())
pVkCmdUpdateBuffer (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdUpdateBufferPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("data" ::: Ptr ())
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("offset" ::: DeviceSize)
      -> ("data" ::: Ptr ())
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("data" ::: Ptr ())
   -> 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 vkCmdUpdateBuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdUpdateBuffer' :: Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdUpdateBuffer' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("data" ::: Ptr ())
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("data" ::: Ptr ())
-> IO ()
mkVkCmdUpdateBuffer FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdUpdateBufferPtr
  Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdUpdateBuffer' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
dstBuffer) ("offset" ::: DeviceSize
dstOffset) ("offset" ::: DeviceSize
dataSize) ("data" ::: Ptr ()
data')
  () -> 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" mkVkCmdFillBuffer
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> DeviceSize -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> DeviceSize -> Word32 -> IO ()

-- | vkCmdFillBuffer - Fill a region of a buffer with a fixed value
--
-- = Description
--
-- 'cmdFillBuffer' is treated as “transfer” operation for the purposes of
-- synchronization barriers. The
-- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
-- /must/ be specified in @usage@ of
-- 'Vulkan.Core10.Buffer.BufferCreateInfo' in order for the buffer to be
-- compatible with 'cmdFillBuffer'.
--
-- == Valid Usage
--
-- -   @dstOffset@ /must/ be less than the size of @dstBuffer@
--
-- -   @dstOffset@ /must/ be a multiple of @4@
--
-- -   If @size@ is not equal to 'Vulkan.Core10.APIConstants.WHOLE_SIZE',
--     @size@ /must/ be greater than @0@
--
-- -   If @size@ is not equal to 'Vulkan.Core10.APIConstants.WHOLE_SIZE',
--     @size@ /must/ be less than or equal to the size of @dstBuffer@ minus
--     @dstOffset@
--
-- -   If @size@ is not equal to 'Vulkan.Core10.APIConstants.WHOLE_SIZE',
--     @size@ /must/ be a multiple of @4@
--
-- -   @dstBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   If @commandBuffer@ is an unprotected command buffer, then
--     @dstBuffer@ /must/ not be a protected buffer
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstBuffer@
--     /must/ not be an unprotected buffer
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @dstBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' 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 transfer, graphics or compute
--     operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Both of @commandBuffer@, and @dstBuffer@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdFillBuffer :: forall io
               . (MonadIO io)
              => -- | @commandBuffer@ is the command buffer into which the command will be
                 -- recorded.
                 CommandBuffer
              -> -- | @dstBuffer@ is the buffer to be filled.
                 ("dstBuffer" ::: Buffer)
              -> -- | @dstOffset@ is the byte offset into the buffer at which to start
                 -- filling, and /must/ be a multiple of 4.
                 ("dstOffset" ::: DeviceSize)
              -> -- | @size@ is the number of bytes to fill, and /must/ be either a multiple
                 -- of 4, or 'Vulkan.Core10.APIConstants.WHOLE_SIZE' to fill the range from
                 -- @offset@ to the end of the buffer. If
                 -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE' is used and the remaining size
                 -- of the buffer is not a multiple of 4, then the nearest smaller multiple
                 -- is used.
                 DeviceSize
              -> -- | @data@ is the 4-byte word written repeatedly to the buffer to fill
                 -- @size@ bytes of data. The data word is written to memory according to
                 -- the host endianness.
                 ("data" ::: Word32)
              -> io ()
cmdFillBuffer :: CommandBuffer
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> io ()
cmdFillBuffer commandBuffer :: CommandBuffer
commandBuffer dstBuffer :: Buffer
dstBuffer dstOffset :: "offset" ::: DeviceSize
dstOffset size :: "offset" ::: DeviceSize
size data' :: "firstViewport" ::: Word32
data' = 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 vkCmdFillBufferPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdFillBufferPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("offset" ::: DeviceSize)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdFillBuffer (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdFillBufferPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("offset" ::: DeviceSize)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: 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 vkCmdFillBuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdFillBuffer' :: Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdFillBuffer' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdFillBuffer FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdFillBufferPtr
  Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdFillBuffer' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
dstBuffer) ("offset" ::: DeviceSize
dstOffset) ("offset" ::: DeviceSize
size) ("firstViewport" ::: Word32
data')
  () -> 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" mkVkCmdClearColorImage
  :: FunPtr (Ptr CommandBuffer_T -> Image -> ImageLayout -> Ptr ClearColorValue -> Word32 -> Ptr ImageSubresourceRange -> IO ()) -> Ptr CommandBuffer_T -> Image -> ImageLayout -> Ptr ClearColorValue -> Word32 -> Ptr ImageSubresourceRange -> IO ()

-- | vkCmdClearColorImage - Clear regions of a color image
--
-- = Description
--
-- Each specified range in @pRanges@ is cleared to the value specified by
-- @pColor@.
--
-- == Valid Usage
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @image@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT'
--
-- -   @image@ /must/ have been created with
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   @image@ /must/ not use a format listed in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion>
--
-- -   If @image@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @imageLayout@ /must/ specify the layout of the image subresource
--     ranges of @image@ specified in @pRanges@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @imageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
--
-- -   The 'Vulkan.Core10.ImageView.ImageSubresourceRange'::@aspectMask@
--     members of the elements of the @pRanges@ array /must/ each only
--     include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'
--
-- -   The 'Vulkan.Core10.ImageView.ImageSubresourceRange'::@baseMipLevel@
--     members of the elements of the @pRanges@ array /must/ each be less
--     than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created
--
-- -   For each 'Vulkan.Core10.ImageView.ImageSubresourceRange' element of
--     @pRanges@, if the @levelCount@ member is not
--     'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS', then
--     @baseMipLevel@ + @levelCount@ /must/ be less than the @mipLevels@
--     specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was
--     created
--
-- -   The
--     'Vulkan.Core10.ImageView.ImageSubresourceRange'::@baseArrayLayer@
--     members of the elements of the @pRanges@ array /must/ each be less
--     than the @arrayLayers@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created
--
-- -   For each 'Vulkan.Core10.ImageView.ImageSubresourceRange' element of
--     @pRanges@, if the @layerCount@ member is not
--     'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', then
--     @baseArrayLayer@ + @layerCount@ /must/ be less than the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @image@ was created
--
-- -   @image@ /must/ not have a compressed or depth\/stencil format
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @image@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then @image@
--     /must/ not be an unprotected image
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @image@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @imageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @pColor@ /must/ be a valid pointer to a valid 'ClearColorValue'
--     union
--
-- -   @pRanges@ /must/ be a valid pointer to an array of @rangeCount@
--     valid 'Vulkan.Core10.ImageView.ImageSubresourceRange' structures
--
-- -   @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, or compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @rangeCount@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and @image@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'ClearColorValue', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout',
-- 'Vulkan.Core10.ImageView.ImageSubresourceRange'
cmdClearColorImage :: forall io
                    . (MonadIO io)
                   => -- | @commandBuffer@ is the command buffer into which the command will be
                      -- recorded.
                      CommandBuffer
                   -> -- | @image@ is the image to be cleared.
                      Image
                   -> -- | @imageLayout@ specifies the current layout of the image subresource
                      -- ranges to be cleared, and /must/ be
                      -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR',
                      -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL' or
                      -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'.
                      ImageLayout
                   -> -- | @pColor@ is a pointer to a 'ClearColorValue' structure containing the
                      -- values that the image subresource ranges will be cleared to (see
                      -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears-values>
                      -- below).
                      ClearColorValue
                   -> -- | @pRanges@ is a pointer to an array of
                      -- 'Vulkan.Core10.ImageView.ImageSubresourceRange' structures describing a
                      -- range of mipmap levels, array layers, and aspects to be cleared, as
                      -- described in
                      -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-views Image Views>.
                      ("ranges" ::: Vector ImageSubresourceRange)
                   -> io ()
cmdClearColorImage :: CommandBuffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ClearColorValue
-> ("ranges" ::: Vector ImageSubresourceRange)
-> io ()
cmdClearColorImage commandBuffer :: CommandBuffer
commandBuffer image :: "srcImage" ::: Image
image imageLayout :: "srcImageLayout" ::: ImageLayout
imageLayout color :: ClearColorValue
color ranges :: "ranges" ::: Vector ImageSubresourceRange
ranges = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdClearColorImagePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pColor" ::: Ptr ClearColorValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
vkCmdClearColorImagePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("pColor" ::: Ptr ClearColorValue)
      -> ("firstViewport" ::: Word32)
      -> ("pRanges" ::: Ptr ImageSubresourceRange)
      -> IO ())
pVkCmdClearColorImage (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pColor" ::: Ptr ClearColorValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
vkCmdClearColorImagePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pColor" ::: Ptr ClearColorValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("pColor" ::: Ptr ClearColorValue)
      -> ("firstViewport" ::: Word32)
      -> ("pRanges" ::: Ptr ImageSubresourceRange)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pColor" ::: Ptr ClearColorValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> 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 vkCmdClearColorImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdClearColorImage' :: Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("pColor" ::: Ptr ClearColorValue)
-> ("firstViewport" ::: Word32)
-> ("pRanges" ::: Ptr ImageSubresourceRange)
-> IO ()
vkCmdClearColorImage' = FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pColor" ::: Ptr ClearColorValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("pColor" ::: Ptr ClearColorValue)
-> ("firstViewport" ::: Word32)
-> ("pRanges" ::: Ptr ImageSubresourceRange)
-> IO ()
mkVkCmdClearColorImage FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pColor" ::: Ptr ClearColorValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
vkCmdClearColorImagePtr
  "pColor" ::: Ptr ClearColorValue
pColor <- ((("pColor" ::: Ptr ClearColorValue) -> IO ()) -> IO ())
-> ContT () IO ("pColor" ::: Ptr ClearColorValue)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pColor" ::: Ptr ClearColorValue) -> IO ()) -> IO ())
 -> ContT () IO ("pColor" ::: Ptr ClearColorValue))
-> ((("pColor" ::: Ptr ClearColorValue) -> IO ()) -> IO ())
-> ContT () IO ("pColor" ::: Ptr ClearColorValue)
forall a b. (a -> b) -> a -> b
$ ClearColorValue
-> (("pColor" ::: Ptr ClearColorValue) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ClearColorValue
color)
  "pRanges" ::: Ptr ImageSubresourceRange
pPRanges <- ((("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) -> IO ())
-> ContT () IO ("pRanges" ::: Ptr ImageSubresourceRange)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) -> IO ())
 -> ContT () IO ("pRanges" ::: Ptr ImageSubresourceRange))
-> ((("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) -> IO ())
-> ContT () IO ("pRanges" ::: Ptr ImageSubresourceRange)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pRanges" ::: Ptr ImageSubresourceRange) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageSubresourceRange ((("ranges" ::: Vector ImageSubresourceRange) -> Int
forall a. Vector a -> Int
Data.Vector.length ("ranges" ::: Vector ImageSubresourceRange
ranges)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 20) 4
  (Int -> ImageSubresourceRange -> ContT () IO ())
-> ("ranges" ::: Vector ImageSubresourceRange) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageSubresourceRange
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRanges" ::: Ptr ImageSubresourceRange)
-> ImageSubresourceRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRanges" ::: Ptr ImageSubresourceRange
pPRanges ("pRanges" ::: Ptr ImageSubresourceRange)
-> Int -> "pRanges" ::: Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (20 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageSubresourceRange) (ImageSubresourceRange
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("ranges" ::: Vector ImageSubresourceRange
ranges)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("pColor" ::: Ptr ClearColorValue)
-> ("firstViewport" ::: Word32)
-> ("pRanges" ::: Ptr ImageSubresourceRange)
-> IO ()
vkCmdClearColorImage' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("srcImage" ::: Image
image) ("srcImageLayout" ::: ImageLayout
imageLayout) "pColor" ::: Ptr ClearColorValue
pColor ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("ranges" ::: Vector ImageSubresourceRange) -> Int
forall a. Vector a -> Int
Data.Vector.length (("ranges" ::: Vector ImageSubresourceRange) -> Int)
-> ("ranges" ::: Vector ImageSubresourceRange) -> Int
forall a b. (a -> b) -> a -> b
$ ("ranges" ::: Vector ImageSubresourceRange
ranges)) :: Word32)) ("pRanges" ::: Ptr ImageSubresourceRange
pPRanges)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdClearDepthStencilImage
  :: FunPtr (Ptr CommandBuffer_T -> Image -> ImageLayout -> Ptr ClearDepthStencilValue -> Word32 -> Ptr ImageSubresourceRange -> IO ()) -> Ptr CommandBuffer_T -> Image -> ImageLayout -> Ptr ClearDepthStencilValue -> Word32 -> Ptr ImageSubresourceRange -> IO ()

-- | vkCmdClearDepthStencilImage - Fill regions of a combined depth\/stencil
-- image
--
-- == Valid Usage
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @image@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT'
--
-- -   If the @aspect@ member of any element of @pRanges@ includes
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT',
--     and @image@ was created with
--     <VkImageStencilUsageCreateInfo.html separate stencil usage>,
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     /must/ have been included in the
--     'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo'::@stencilUsage@
--     used to create @image@
--
-- -   If the @aspect@ member of any element of @pRanges@ includes
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT',
--     and @image@ was not created with
--     <VkImageStencilUsageCreateInfo.html separate stencil usage>,
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     /must/ have been included in the
--     'Vulkan.Core10.Image.ImageCreateInfo'::@usage@ used to create
--     @image@
--
-- -   If the @aspect@ member of any element of @pRanges@ includes
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT',
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--     /must/ have been included in the
--     'Vulkan.Core10.Image.ImageCreateInfo'::@usage@ used to create
--     @image@
--
-- -   If @image@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @imageLayout@ /must/ specify the layout of the image subresource
--     ranges of @image@ specified in @pRanges@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @imageLayout@ /must/ be either of
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'
--     or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL'
--
-- -   The 'Vulkan.Core10.ImageView.ImageSubresourceRange'::@aspectMask@
--     member of each element of the @pRanges@ array /must/ not include
--     bits other than
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--
-- -   If the @image@’s format does not have a stencil component, then the
--     'Vulkan.Core10.ImageView.ImageSubresourceRange'::@aspectMask@ member
--     of each element of the @pRanges@ array /must/ not include the
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--     bit
--
-- -   If the @image@’s format does not have a depth component, then the
--     'Vulkan.Core10.ImageView.ImageSubresourceRange'::@aspectMask@ member
--     of each element of the @pRanges@ array /must/ not include the
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' bit
--
-- -   The 'Vulkan.Core10.ImageView.ImageSubresourceRange'::@baseMipLevel@
--     members of the elements of the @pRanges@ array /must/ each be less
--     than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created
--
-- -   For each 'Vulkan.Core10.ImageView.ImageSubresourceRange' element of
--     @pRanges@, if the @levelCount@ member is not
--     'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS', then
--     @baseMipLevel@ + @levelCount@ /must/ be less than the @mipLevels@
--     specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was
--     created
--
-- -   The
--     'Vulkan.Core10.ImageView.ImageSubresourceRange'::@baseArrayLayer@
--     members of the elements of the @pRanges@ array /must/ each be less
--     than the @arrayLayers@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created
--
-- -   For each 'Vulkan.Core10.ImageView.ImageSubresourceRange' element of
--     @pRanges@, if the @layerCount@ member is not
--     'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', then
--     @baseArrayLayer@ + @layerCount@ /must/ be less than the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @image@ was created
--
-- -   @image@ /must/ have a depth\/stencil format
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @image@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then @image@
--     /must/ not be an unprotected image
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @image@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @imageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @pDepthStencil@ /must/ be a valid pointer to a valid
--     'ClearDepthStencilValue' structure
--
-- -   @pRanges@ /must/ be a valid pointer to an array of @rangeCount@
--     valid 'Vulkan.Core10.ImageView.ImageSubresourceRange' structures
--
-- -   @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 operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @rangeCount@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and @image@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'ClearDepthStencilValue', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout',
-- 'Vulkan.Core10.ImageView.ImageSubresourceRange'
cmdClearDepthStencilImage :: forall io
                           . (MonadIO io)
                          => -- | @commandBuffer@ is the command buffer into which the command will be
                             -- recorded.
                             CommandBuffer
                          -> -- | @image@ is the image to be cleared.
                             Image
                          -> -- | @imageLayout@ specifies the current layout of the image subresource
                             -- ranges to be cleared, and /must/ be
                             -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL' or
                             -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'.
                             ImageLayout
                          -> -- | @pDepthStencil@ is a pointer to a 'ClearDepthStencilValue' structure
                             -- containing the values that the depth and stencil image subresource
                             -- ranges will be cleared to (see
                             -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears-values>
                             -- below).
                             ClearDepthStencilValue
                          -> -- | @pRanges@ is a pointer to an array of
                             -- 'Vulkan.Core10.ImageView.ImageSubresourceRange' structures describing a
                             -- range of mipmap levels, array layers, and aspects to be cleared, as
                             -- described in
                             -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-views Image Views>.
                             ("ranges" ::: Vector ImageSubresourceRange)
                          -> io ()
cmdClearDepthStencilImage :: CommandBuffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ClearDepthStencilValue
-> ("ranges" ::: Vector ImageSubresourceRange)
-> io ()
cmdClearDepthStencilImage commandBuffer :: CommandBuffer
commandBuffer image :: "srcImage" ::: Image
image imageLayout :: "srcImageLayout" ::: ImageLayout
imageLayout depthStencil :: ClearDepthStencilValue
depthStencil ranges :: "ranges" ::: Vector ImageSubresourceRange
ranges = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdClearDepthStencilImagePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
vkCmdClearDepthStencilImagePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
      -> ("firstViewport" ::: Word32)
      -> ("pRanges" ::: Ptr ImageSubresourceRange)
      -> IO ())
pVkCmdClearDepthStencilImage (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
vkCmdClearDepthStencilImagePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
      -> ("firstViewport" ::: Word32)
      -> ("pRanges" ::: Ptr ImageSubresourceRange)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> 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 vkCmdClearDepthStencilImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdClearDepthStencilImage' :: Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> ("firstViewport" ::: Word32)
-> ("pRanges" ::: Ptr ImageSubresourceRange)
-> IO ()
vkCmdClearDepthStencilImage' = FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> ("firstViewport" ::: Word32)
-> ("pRanges" ::: Ptr ImageSubresourceRange)
-> IO ()
mkVkCmdClearDepthStencilImage FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
   -> ("firstViewport" ::: Word32)
   -> ("pRanges" ::: Ptr ImageSubresourceRange)
   -> IO ())
vkCmdClearDepthStencilImagePtr
  "pDepthStencil" ::: Ptr ClearDepthStencilValue
pDepthStencil <- ((("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO ())
 -> IO ())
-> ContT () IO ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO ())
  -> IO ())
 -> ContT () IO ("pDepthStencil" ::: Ptr ClearDepthStencilValue))
-> ((("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO ())
    -> IO ())
-> ContT () IO ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
forall a b. (a -> b) -> a -> b
$ ClearDepthStencilValue
-> (("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ClearDepthStencilValue
depthStencil)
  "pRanges" ::: Ptr ImageSubresourceRange
pPRanges <- ((("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) -> IO ())
-> ContT () IO ("pRanges" ::: Ptr ImageSubresourceRange)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) -> IO ())
 -> ContT () IO ("pRanges" ::: Ptr ImageSubresourceRange))
-> ((("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) -> IO ())
-> ContT () IO ("pRanges" ::: Ptr ImageSubresourceRange)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pRanges" ::: Ptr ImageSubresourceRange) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageSubresourceRange ((("ranges" ::: Vector ImageSubresourceRange) -> Int
forall a. Vector a -> Int
Data.Vector.length ("ranges" ::: Vector ImageSubresourceRange
ranges)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 20) 4
  (Int -> ImageSubresourceRange -> ContT () IO ())
-> ("ranges" ::: Vector ImageSubresourceRange) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageSubresourceRange
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRanges" ::: Ptr ImageSubresourceRange)
-> ImageSubresourceRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRanges" ::: Ptr ImageSubresourceRange
pPRanges ("pRanges" ::: Ptr ImageSubresourceRange)
-> Int -> "pRanges" ::: Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (20 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageSubresourceRange) (ImageSubresourceRange
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("ranges" ::: Vector ImageSubresourceRange
ranges)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> ("firstViewport" ::: Word32)
-> ("pRanges" ::: Ptr ImageSubresourceRange)
-> IO ()
vkCmdClearDepthStencilImage' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("srcImage" ::: Image
image) ("srcImageLayout" ::: ImageLayout
imageLayout) "pDepthStencil" ::: Ptr ClearDepthStencilValue
pDepthStencil ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("ranges" ::: Vector ImageSubresourceRange) -> Int
forall a. Vector a -> Int
Data.Vector.length (("ranges" ::: Vector ImageSubresourceRange) -> Int)
-> ("ranges" ::: Vector ImageSubresourceRange) -> Int
forall a b. (a -> b) -> a -> b
$ ("ranges" ::: Vector ImageSubresourceRange
ranges)) :: Word32)) ("pRanges" ::: Ptr ImageSubresourceRange
pPRanges)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdClearAttachments - Clear regions within bound framebuffer
-- attachments
--
-- = Description
--
-- 'cmdClearAttachments' /can/ clear multiple regions of each attachment
-- used in the current subpass of a render pass instance. This command
-- /must/ be called only inside a render pass instance, and implicitly
-- selects the images to clear based on the current framebuffer attachments
-- and the command parameters.
--
-- If the render pass has a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-fragmentdensitymapattachment fragment density map attachment>,
-- clears follow the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragmentdensitymapops operations of fragment density maps>
-- as if each clear region was a primitive which generates fragments. The
-- clear color is applied to all pixels inside each fragment’s area
-- regardless if the pixels lie outside of the clear region. Clears /may/
-- have a different set of supported fragment areas than draws.
--
-- Unlike other
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears clear commands>,
-- 'cmdClearAttachments' executes as a drawing command, rather than a
-- transfer command, with writes performed by it executing in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primrast-order rasterization order>.
-- Clears to color attachments are executed as color attachment writes, by
-- the
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT'
-- stage. Clears to depth\/stencil attachments are executed as
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth depth writes>
-- and
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil writes>
-- by the
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_EARLY_FRAGMENT_TESTS_BIT'
-- and
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_LATE_FRAGMENT_TESTS_BIT'
-- stages.
--
-- == Valid Usage
--
-- -   If the @aspectMask@ member of any element of @pAttachments@ contains
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT',
--     then the @colorAttachment@ member of that element /must/ either
--     refer to a color attachment which is
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', or /must/ be a valid
--     color attachment
--
-- -   If the @aspectMask@ member of any element of @pAttachments@ contains
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT',
--     then the current subpass\' depth\/stencil attachment /must/ either
--     be 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', or /must/ have a
--     depth component
--
-- -   If the @aspectMask@ member of any element of @pAttachments@ contains
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT',
--     then the current subpass\' depth\/stencil attachment /must/ either
--     be 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', or /must/ have a
--     stencil component
--
-- -   The @rect@ member of each element of @pRects@ /must/ have an
--     @extent.width@ greater than @0@
--
-- -   The @rect@ member of each element of @pRects@ /must/ have an
--     @extent.height@ greater than @0@
--
-- -   The rectangular region specified by each element of @pRects@ /must/
--     be contained within the render area of the current render pass
--     instance
--
-- -   The layers specified by each element of @pRects@ /must/ be contained
--     within every attachment that @pAttachments@ refers to
--
-- -   The @layerCount@ member of each element of @pRects@ /must/ not be
--     @0@
--
-- -   If @commandBuffer@ is an unprotected command buffer, then each
--     attachment to be cleared /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then each
--     attachment to be cleared /must/ not be an unprotected image
--
-- -   If the render pass instance this is recorded in uses multiview, then
--     @baseArrayLayer@ /must/ be zero and @layerCount@ /must/ be one
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pAttachments@ /must/ be a valid pointer to an array of
--     @attachmentCount@ valid 'ClearAttachment' structures
--
-- -   @pRects@ /must/ be a valid pointer to an array of @rectCount@
--     'ClearRect' structures
--
-- -   @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 operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   @attachmentCount@ /must/ be greater than @0@
--
-- -   @rectCount@ /must/ be greater than @0@
--
-- == 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'ClearAttachment', 'ClearRect', 'Vulkan.Core10.Handles.CommandBuffer'
cmdClearAttachments :: forall io
                     . (MonadIO io)
                    => -- | @commandBuffer@ is the command buffer into which the command will be
                       -- recorded.
                       CommandBuffer
                    -> -- | @pAttachments@ is a pointer to an array of 'ClearAttachment' structures
                       -- defining the attachments to clear and the clear values to use. If any
                       -- attachment to be cleared in the current subpass is
                       -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', then the clear has no
                       -- effect on that attachment.
                       ("attachments" ::: Vector ClearAttachment)
                    -> -- | @pRects@ is a pointer to an array of 'ClearRect' structures defining
                       -- regions within each selected attachment to clear.
                       ("rects" ::: Vector ClearRect)
                    -> io ()
cmdClearAttachments :: CommandBuffer
-> ("attachments" ::: Vector ClearAttachment)
-> ("rects" ::: Vector ClearRect)
-> io ()
cmdClearAttachments commandBuffer :: CommandBuffer
commandBuffer attachments :: "attachments" ::: Vector ClearAttachment
attachments rects :: "rects" ::: Vector ClearRect
rects = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdClearAttachmentsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pAttachments" ::: Ptr ClearAttachment)
   -> ("firstViewport" ::: Word32)
   -> ("pRects" ::: Ptr ClearRect)
   -> IO ())
vkCmdClearAttachmentsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("pAttachments" ::: Ptr ClearAttachment)
      -> ("firstViewport" ::: Word32)
      -> ("pRects" ::: Ptr ClearRect)
      -> IO ())
pVkCmdClearAttachments (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pAttachments" ::: Ptr ClearAttachment)
   -> ("firstViewport" ::: Word32)
   -> ("pRects" ::: Ptr ClearRect)
   -> IO ())
vkCmdClearAttachmentsPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pAttachments" ::: Ptr ClearAttachment)
   -> ("firstViewport" ::: Word32)
   -> ("pRects" ::: Ptr ClearRect)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("pAttachments" ::: Ptr ClearAttachment)
      -> ("firstViewport" ::: Word32)
      -> ("pRects" ::: Ptr ClearRect)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pAttachments" ::: Ptr ClearAttachment)
   -> ("firstViewport" ::: Word32)
   -> ("pRects" ::: Ptr ClearRect)
   -> 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 vkCmdClearAttachments is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdClearAttachments' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("pAttachments" ::: Ptr ClearAttachment)
-> ("firstViewport" ::: Word32)
-> ("pRects" ::: Ptr ClearRect)
-> IO ()
vkCmdClearAttachments' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pAttachments" ::: Ptr ClearAttachment)
   -> ("firstViewport" ::: Word32)
   -> ("pRects" ::: Ptr ClearRect)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("pAttachments" ::: Ptr ClearAttachment)
-> ("firstViewport" ::: Word32)
-> ("pRects" ::: Ptr ClearRect)
-> IO ()
mkVkCmdClearAttachments FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pAttachments" ::: Ptr ClearAttachment)
   -> ("firstViewport" ::: Word32)
   -> ("pRects" ::: Ptr ClearRect)
   -> IO ())
vkCmdClearAttachmentsPtr
  "pAttachments" ::: Ptr ClearAttachment
pPAttachments <- ((("pAttachments" ::: Ptr ClearAttachment) -> IO ()) -> IO ())
-> ContT () IO ("pAttachments" ::: Ptr ClearAttachment)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAttachments" ::: Ptr ClearAttachment) -> IO ()) -> IO ())
 -> ContT () IO ("pAttachments" ::: Ptr ClearAttachment))
-> ((("pAttachments" ::: Ptr ClearAttachment) -> IO ()) -> IO ())
-> ContT () IO ("pAttachments" ::: Ptr ClearAttachment)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pAttachments" ::: Ptr ClearAttachment) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ClearAttachment ((("attachments" ::: Vector ClearAttachment) -> Int
forall a. Vector a -> Int
Data.Vector.length ("attachments" ::: Vector ClearAttachment
attachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 4
  (Int -> ClearAttachment -> ContT () IO ())
-> ("attachments" ::: Vector ClearAttachment) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ClearAttachment
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pAttachments" ::: Ptr ClearAttachment)
-> ClearAttachment -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pAttachments" ::: Ptr ClearAttachment
pPAttachments ("pAttachments" ::: Ptr ClearAttachment)
-> Int -> "pAttachments" ::: Ptr ClearAttachment
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ClearAttachment) (ClearAttachment
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("attachments" ::: Vector ClearAttachment
attachments)
  "pRects" ::: Ptr ClearRect
pPRects <- ((("pRects" ::: Ptr ClearRect) -> IO ()) -> IO ())
-> ContT () IO ("pRects" ::: Ptr ClearRect)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRects" ::: Ptr ClearRect) -> IO ()) -> IO ())
 -> ContT () IO ("pRects" ::: Ptr ClearRect))
-> ((("pRects" ::: Ptr ClearRect) -> IO ()) -> IO ())
-> ContT () IO ("pRects" ::: Ptr ClearRect)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pRects" ::: Ptr ClearRect) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ClearRect ((("rects" ::: Vector ClearRect) -> Int
forall a. Vector a -> Int
Data.Vector.length ("rects" ::: Vector ClearRect
rects)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 4
  (Int -> ClearRect -> ContT () IO ())
-> ("rects" ::: Vector ClearRect) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ClearRect
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRects" ::: Ptr ClearRect) -> ClearRect -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRects" ::: Ptr ClearRect
pPRects ("pRects" ::: Ptr ClearRect) -> Int -> "pRects" ::: Ptr ClearRect
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ClearRect) (ClearRect
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("rects" ::: Vector ClearRect
rects)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("pAttachments" ::: Ptr ClearAttachment)
-> ("firstViewport" ::: Word32)
-> ("pRects" ::: Ptr ClearRect)
-> IO ()
vkCmdClearAttachments' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("attachments" ::: Vector ClearAttachment) -> Int
forall a. Vector a -> Int
Data.Vector.length (("attachments" ::: Vector ClearAttachment) -> Int)
-> ("attachments" ::: Vector ClearAttachment) -> Int
forall a b. (a -> b) -> a -> b
$ ("attachments" ::: Vector ClearAttachment
attachments)) :: Word32)) ("pAttachments" ::: Ptr ClearAttachment
pPAttachments) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("rects" ::: Vector ClearRect) -> Int
forall a. Vector a -> Int
Data.Vector.length (("rects" ::: Vector ClearRect) -> Int)
-> ("rects" ::: Vector ClearRect) -> Int
forall a b. (a -> b) -> a -> b
$ ("rects" ::: Vector ClearRect
rects)) :: Word32)) ("pRects" ::: Ptr ClearRect
pPRects)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdResolveImage - Resolve regions of an image
--
-- = Description
--
-- During the resolve the samples corresponding to each pixel location in
-- the source are converted to a single sample before being written to the
-- destination. If the source formats are floating-point or normalized
-- types, the sample values for each pixel are resolved in an
-- implementation-dependent manner. If the source formats are integer
-- types, a single sample’s value is selected for each pixel.
--
-- @srcOffset@ and @dstOffset@ select the initial @x@, @y@, and @z@ offsets
-- in texels of the sub-regions of the source and destination image data.
-- @extent@ is the size in texels of the source image to resolve in
-- @width@, @height@ and @depth@. Each element of @pRegions@ /must/ be a
-- region that is contained within its corresponding image.
--
-- Resolves are done layer by layer starting with @baseArrayLayer@ member
-- of @srcSubresource@ for the source and @dstSubresource@ for the
-- destination. @layerCount@ layers are resolved to the destination image.
--
-- == Valid Usage
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @srcImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is an unprotected command buffer, then @dstImage@
--     /must/ not be a protected image
--
-- -   If @commandBuffer@ is a protected command buffer, then @dstImage@
--     /must/ not be an unprotected image
--
-- -   The union of all source regions, and the union of all destination
--     regions, specified by the elements of @pRegions@, /must/ not overlap
--     in memory
--
-- -   If @srcImage@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @srcImage@ /must/ have a sample count equal to any valid sample
--     count value other than
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   If @dstImage@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @dstImage@ /must/ have a sample count equal to
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   @srcImageLayout@ /must/ specify the layout of the image subresources
--     of @srcImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @srcImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL'
--     or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL'
--
-- -   @dstImageLayout@ /must/ specify the layout of the image subresources
--     of @dstImage@ specified in @pRegions@ at the time this command is
--     executed on a 'Vulkan.Core10.Handles.Device'
--
-- -   @dstImageLayout@ /must/ be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'
--     or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL'
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     of @dstImage@ /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   @srcImage@ and @dstImage@ /must/ have been created with the same
--     image format
--
-- -   The @srcSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ was created
--
-- -   The @dstSubresource.mipLevel@ member of each element of @pRegions@
--     /must/ be less than the @mipLevels@ specified in
--     'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ was created
--
-- -   The @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of
--     each element of @pRegions@ /must/ be less than or equal to the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @srcImage@ was created
--
-- -   The @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of
--     each element of @pRegions@ /must/ be less than or equal to the
--     @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo'
--     when @dstImage@ was created
--
-- -   @dstImage@ and @srcImage@ /must/ not have been created with @flags@
--     containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT'
--
-- -   If either @srcImage@ or @dstImage@ are of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element
--     of @pRegions@, @srcSubresource.baseArrayLayer@ /must/ be @0@ and
--     @srcSubresource.layerCount@ /must/ be @1@
--
-- -   If either @srcImage@ or @dstImage@ are of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element
--     of @pRegions@, @dstSubresource.baseArrayLayer@ /must/ be @0@ and
--     @dstSubresource.layerCount@ /must/ be @1@
--
-- -   For each element of @pRegions@, @srcOffset.x@ and (@extent.width@ +
--     @srcOffset.x@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the width of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   For each element of @pRegions@, @srcOffset.y@ and (@extent.height@ +
--     @srcOffset.y@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the height of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @srcOffset.y@ /must/ be @0@ and @extent.height@
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @srcOffset.z@ and (@extent.depth@ +
--     @srcOffset.z@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the depth of the specified @srcSubresource@ of
--     @srcImage@
--
-- -   If @srcImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' or
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @srcOffset.z@ /must/ be @0@ and @extent.depth@ /must/
--     be @1@
--
-- -   For each element of @pRegions@, @dstOffset.x@ and (@extent.width@ +
--     @dstOffset.x@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the width of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   For each element of @pRegions@, @dstOffset.y@ and (@extent.height@ +
--     @dstOffset.y@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the height of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element
--     of @pRegions@, @dstOffset.y@ /must/ be @0@ and @extent.height@
--     /must/ be @1@
--
-- -   For each element of @pRegions@, @dstOffset.z@ and (@extent.depth@ +
--     @dstOffset.z@) /must/ both be greater than or equal to @0@ and less
--     than or equal to the depth of the specified @dstSubresource@ of
--     @dstImage@
--
-- -   If @dstImage@ is of type
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' or
--     'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element
--     of @pRegions@, @dstOffset.z@ /must/ be @0@ and @extent.depth@ /must/
--     be @1@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @srcImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @dstImage@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   @dstImageLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @pRegions@ /must/ be a valid pointer to an array of @regionCount@
--     valid 'ImageResolve' structures
--
-- -   @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 operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @regionCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @dstImage@, and @srcImage@ /must/ have been
--     created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout', 'ImageResolve'
cmdResolveImage :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command will be
                   -- recorded.
                   CommandBuffer
                -> -- | @srcImage@ is the source image.
                   ("srcImage" ::: Image)
                -> -- | @srcImageLayout@ is the layout of the source image subresources for the
                   -- resolve.
                   ("srcImageLayout" ::: ImageLayout)
                -> -- | @dstImage@ is the destination image.
                   ("dstImage" ::: Image)
                -> -- | @dstImageLayout@ is the layout of the destination image subresources for
                   -- the resolve.
                   ("dstImageLayout" ::: ImageLayout)
                -> -- | @pRegions@ is a pointer to an array of 'ImageResolve' structures
                   -- specifying the regions to resolve.
                   ("regions" ::: Vector ImageResolve)
                -> io ()
cmdResolveImage :: CommandBuffer
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("regions" ::: Vector ImageResolve)
-> io ()
cmdResolveImage commandBuffer :: CommandBuffer
commandBuffer srcImage :: "srcImage" ::: Image
srcImage srcImageLayout :: "srcImageLayout" ::: ImageLayout
srcImageLayout dstImage :: "srcImage" ::: Image
dstImage dstImageLayout :: "srcImageLayout" ::: ImageLayout
dstImageLayout regions :: "regions" ::: Vector ImageResolve
regions = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdResolveImagePtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageResolve)
   -> IO ())
vkCmdResolveImagePtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr ImageResolve)
      -> IO ())
pVkCmdResolveImage (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageResolve)
   -> IO ())
vkCmdResolveImagePtr FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageResolve)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("srcImage" ::: Image)
      -> ("srcImageLayout" ::: ImageLayout)
      -> ("firstViewport" ::: Word32)
      -> ("pRegions" ::: Ptr ImageResolve)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageResolve)
   -> 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 vkCmdResolveImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdResolveImage' :: Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageResolve)
-> IO ()
vkCmdResolveImage' = FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageResolve)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageResolve)
-> IO ()
mkVkCmdResolveImage FunPtr
  (Ptr CommandBuffer_T
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("srcImage" ::: Image)
   -> ("srcImageLayout" ::: ImageLayout)
   -> ("firstViewport" ::: Word32)
   -> ("pRegions" ::: Ptr ImageResolve)
   -> IO ())
vkCmdResolveImagePtr
  "pRegions" ::: Ptr ImageResolve
pPRegions <- ((("pRegions" ::: Ptr ImageResolve) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr ImageResolve)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRegions" ::: Ptr ImageResolve) -> IO ()) -> IO ())
 -> ContT () IO ("pRegions" ::: Ptr ImageResolve))
-> ((("pRegions" ::: Ptr ImageResolve) -> IO ()) -> IO ())
-> ContT () IO ("pRegions" ::: Ptr ImageResolve)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pRegions" ::: Ptr ImageResolve) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageResolve ((("regions" ::: Vector ImageResolve) -> Int
forall a. Vector a -> Int
Data.Vector.length ("regions" ::: Vector ImageResolve
regions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 68) 4
  (Int -> ImageResolve -> ContT () IO ())
-> ("regions" ::: Vector ImageResolve) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageResolve
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pRegions" ::: Ptr ImageResolve) -> ImageResolve -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pRegions" ::: Ptr ImageResolve
pPRegions ("pRegions" ::: Ptr ImageResolve)
-> Int -> "pRegions" ::: Ptr ImageResolve
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (68 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageResolve) (ImageResolve
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("regions" ::: Vector ImageResolve
regions)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("srcImage" ::: Image)
-> ("srcImageLayout" ::: ImageLayout)
-> ("firstViewport" ::: Word32)
-> ("pRegions" ::: Ptr ImageResolve)
-> IO ()
vkCmdResolveImage' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("srcImage" ::: Image
srcImage) ("srcImageLayout" ::: ImageLayout
srcImageLayout) ("srcImage" ::: Image
dstImage) ("srcImageLayout" ::: ImageLayout
dstImageLayout) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("regions" ::: Vector ImageResolve) -> Int
forall a. Vector a -> Int
Data.Vector.length (("regions" ::: Vector ImageResolve) -> Int)
-> ("regions" ::: Vector ImageResolve) -> Int
forall a b. (a -> b) -> a -> b
$ ("regions" ::: Vector ImageResolve
regions)) :: Word32)) ("pRegions" ::: Ptr ImageResolve
pPRegions)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdSetEvent - Set an event object to signaled state
--
-- = Description
--
-- When 'cmdSetEvent' is submitted to a queue, it defines an execution
-- dependency on commands that were submitted before it, and defines an
-- event signal operation which sets the event to the signaled state.
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes all commands that occur earlier in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>.
-- The synchronization scope is limited to operations on the pipeline
-- stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>
-- specified by @stageMask@.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes only the event signal operation.
--
-- If @event@ is already in the signaled state when 'cmdSetEvent' is
-- executed on the device, then 'cmdSetEvent' has no effect, no event
-- signal operation occurs, and no execution dependency is generated.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   Any pipeline stage included in @stageMask@ /must/ be supported by
--     the capabilities of the queue family specified by the
--     @queueFamilyIndex@ member of the
--     'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' structure that was
--     used to create the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   @stageMask@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT'
--
-- -   @commandBuffer@’s current device mask /must/ include exactly one
--     physical device
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @event@ /must/ be a valid 'Vulkan.Core10.Handles.Event' handle
--
-- -   @stageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @stageMask@ /must/ not be @0@
--
-- -   @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, or compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Both of @commandBuffer@, and @event@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Event',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags'
cmdSetEvent :: forall io
             . (MonadIO io)
            => -- | @commandBuffer@ is the command buffer into which the command is
               -- recorded.
               CommandBuffer
            -> -- | @event@ is the event that will be signaled.
               Event
            -> -- | @stageMask@ specifies the
               -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask>
               -- used to determine the first
               -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>.
               ("stageMask" ::: PipelineStageFlags)
            -> io ()
cmdSetEvent :: CommandBuffer
-> Event -> ("stageMask" ::: PipelineStageFlags) -> io ()
cmdSetEvent commandBuffer :: CommandBuffer
commandBuffer event :: Event
event stageMask :: "stageMask" ::: PipelineStageFlags
stageMask = 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 vkCmdSetEventPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
vkCmdSetEventPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
pVkCmdSetEvent (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
vkCmdSetEventPtr FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> 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 vkCmdSetEvent is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetEvent' :: Ptr CommandBuffer_T
-> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ()
vkCmdSetEvent' = FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
-> Ptr CommandBuffer_T
-> Event
-> ("stageMask" ::: PipelineStageFlags)
-> IO ()
mkVkCmdSetEvent FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
vkCmdSetEventPtr
  Ptr CommandBuffer_T
-> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ()
vkCmdSetEvent' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Event
event) ("stageMask" ::: PipelineStageFlags
stageMask)
  () -> 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" mkVkCmdResetEvent
  :: FunPtr (Ptr CommandBuffer_T -> Event -> PipelineStageFlags -> IO ()) -> Ptr CommandBuffer_T -> Event -> PipelineStageFlags -> IO ()

-- | vkCmdResetEvent - Reset an event object to non-signaled state
--
-- = Description
--
-- When 'cmdResetEvent' is submitted to a queue, it defines an execution
-- dependency on commands that were submitted before it, and defines an
-- event unsignal operation which resets the event to the unsignaled state.
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes all commands that occur earlier in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>.
-- The synchronization scope is limited to operations on the pipeline
-- stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>
-- specified by @stageMask@.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes only the event unsignal operation.
--
-- If @event@ is already in the unsignaled state when 'cmdResetEvent' is
-- executed on the device, then 'cmdResetEvent' has no effect, no event
-- unsignal operation occurs, and no execution dependency is generated.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @stageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   Any pipeline stage included in @stageMask@ /must/ be supported by
--     the capabilities of the queue family specified by the
--     @queueFamilyIndex@ member of the
--     'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' structure that was
--     used to create the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   @stageMask@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT'
--
-- -   When this command executes, @event@ /must/ not be waited on by a
--     'cmdWaitEvents' command that is currently executing
--
-- -   @commandBuffer@’s current device mask /must/ include exactly one
--     physical device
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @event@ /must/ be a valid 'Vulkan.Core10.Handles.Event' handle
--
-- -   @stageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @stageMask@ /must/ not be @0@
--
-- -   @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, or compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Both of @commandBuffer@, and @event@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Event',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags'
cmdResetEvent :: forall io
               . (MonadIO io)
              => -- | @commandBuffer@ is the command buffer into which the command is
                 -- recorded.
                 CommandBuffer
              -> -- | @event@ is the event that will be unsignaled.
                 Event
              -> -- | @stageMask@ is a bitmask of
                 -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                 -- specifying the
                 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask>
                 -- used to determine when the @event@ is unsignaled.
                 ("stageMask" ::: PipelineStageFlags)
              -> io ()
cmdResetEvent :: CommandBuffer
-> Event -> ("stageMask" ::: PipelineStageFlags) -> io ()
cmdResetEvent commandBuffer :: CommandBuffer
commandBuffer event :: Event
event stageMask :: "stageMask" ::: PipelineStageFlags
stageMask = 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 vkCmdResetEventPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
vkCmdResetEventPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
pVkCmdResetEvent (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
vkCmdResetEventPtr FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> 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 vkCmdResetEvent is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdResetEvent' :: Ptr CommandBuffer_T
-> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ()
vkCmdResetEvent' = FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
-> Ptr CommandBuffer_T
-> Event
-> ("stageMask" ::: PipelineStageFlags)
-> IO ()
mkVkCmdResetEvent FunPtr
  (Ptr CommandBuffer_T
   -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ())
vkCmdResetEventPtr
  Ptr CommandBuffer_T
-> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ()
vkCmdResetEvent' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Event
event) ("stageMask" ::: PipelineStageFlags
stageMask)
  () -> 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" mkVkCmdWaitEventsUnsafe
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()

foreign import ccall
  "dynamic" mkVkCmdWaitEventsSafe
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()

-- | cmdWaitEvents with selectable safeness
cmdWaitEventsSafeOrUnsafe :: forall io
                           . (MonadIO io)
                          => -- No documentation found for TopLevel ""
                             (FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ())
                          -> -- | @commandBuffer@ is the command buffer into which the command is
                             -- recorded.
                             CommandBuffer
                          -> -- | @pEvents@ is a pointer to an array of event object handles to wait on.
                             ("events" ::: Vector Event)
                          -> -- | @srcStageMask@ is a bitmask of
                             -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                             -- specifying the
                             -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask>.
                             ("srcStageMask" ::: PipelineStageFlags)
                          -> -- | @dstStageMask@ is a bitmask of
                             -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                             -- specifying the
                             -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages destination stage mask>.
                             ("dstStageMask" ::: PipelineStageFlags)
                          -> -- | @pMemoryBarriers@ is a pointer to an array of
                             -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' structures.
                             ("memoryBarriers" ::: Vector MemoryBarrier)
                          -> -- | @pBufferMemoryBarriers@ is a pointer to an array of
                             -- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures.
                             ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
                          -> -- | @pImageMemoryBarriers@ is a pointer to an array of
                             -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures.
                             ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
                          -> io ()
cmdWaitEventsSafeOrUnsafe :: (FunPtr
   (Ptr CommandBuffer_T
    -> ("firstViewport" ::: Word32)
    -> Ptr Event
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("firstViewport" ::: Word32)
    -> Ptr MemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr BufferMemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr (SomeStruct ImageMemoryBarrier)
    -> IO ())
 -> Ptr CommandBuffer_T
 -> ("firstViewport" ::: Word32)
 -> Ptr Event
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("firstViewport" ::: Word32)
 -> Ptr MemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr BufferMemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr (SomeStruct ImageMemoryBarrier)
 -> IO ())
-> CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
cmdWaitEventsSafeOrUnsafe mkVkCmdWaitEvents :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> Ptr Event
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
mkVkCmdWaitEvents commandBuffer :: CommandBuffer
commandBuffer events :: "events" ::: Vector Event
events srcStageMask :: "stageMask" ::: PipelineStageFlags
srcStageMask dstStageMask :: "stageMask" ::: PipelineStageFlags
dstStageMask memoryBarriers :: "memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers bufferMemoryBarriers :: "bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers imageMemoryBarriers :: "imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdWaitEventsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
vkCmdWaitEventsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> Ptr Event
      -> ("stageMask" ::: PipelineStageFlags)
      -> ("stageMask" ::: PipelineStageFlags)
      -> ("firstViewport" ::: Word32)
      -> Ptr MemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr BufferMemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr (SomeStruct ImageMemoryBarrier)
      -> IO ())
pVkCmdWaitEvents (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
vkCmdWaitEventsPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> Ptr Event
      -> ("stageMask" ::: PipelineStageFlags)
      -> ("stageMask" ::: PipelineStageFlags)
      -> ("firstViewport" ::: Word32)
      -> Ptr MemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr BufferMemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr (SomeStruct ImageMemoryBarrier)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> 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 vkCmdWaitEvents is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdWaitEvents' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> Ptr Event
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
vkCmdWaitEvents' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> Ptr Event
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
mkVkCmdWaitEvents FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
vkCmdWaitEventsPtr
  Ptr Event
pPEvents <- ((Ptr Event -> IO ()) -> IO ()) -> ContT () IO (Ptr Event)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Event -> IO ()) -> IO ()) -> ContT () IO (Ptr Event))
-> ((Ptr Event -> IO ()) -> IO ()) -> ContT () IO (Ptr Event)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Event -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Event ((("events" ::: Vector Event) -> Int
forall a. Vector a -> Int
Data.Vector.length ("events" ::: Vector Event
events)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Event -> IO ()) -> ("events" ::: Vector Event) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Event
e -> Ptr Event -> Event -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Event
pPEvents Ptr Event -> Int -> Ptr Event
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Event) (Event
e)) ("events" ::: Vector Event
events)
  Ptr MemoryBarrier
pPMemoryBarriers <- ((Ptr MemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr MemoryBarrier)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MemoryBarrier -> IO ()) -> IO ())
 -> ContT () IO (Ptr MemoryBarrier))
-> ((Ptr MemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr MemoryBarrier)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr MemoryBarrier -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @MemoryBarrier ((("memoryBarriers" ::: Vector MemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length ("memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
  (Int -> MemoryBarrier -> ContT () IO ())
-> ("memoryBarriers" ::: Vector MemoryBarrier) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MemoryBarrier
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr MemoryBarrier -> MemoryBarrier -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr MemoryBarrier
pPMemoryBarriers Ptr MemoryBarrier -> Int -> Ptr MemoryBarrier
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryBarrier) (MemoryBarrier
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers)
  Ptr BufferMemoryBarrier
pPBufferMemoryBarriers <- ((Ptr BufferMemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr BufferMemoryBarrier)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr BufferMemoryBarrier -> IO ()) -> IO ())
 -> ContT () IO (Ptr BufferMemoryBarrier))
-> ((Ptr BufferMemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr BufferMemoryBarrier)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr BufferMemoryBarrier -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @BufferMemoryBarrier ((("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
  (Int -> BufferMemoryBarrier -> ContT () IO ())
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: BufferMemoryBarrier
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr BufferMemoryBarrier
pPBufferMemoryBarriers Ptr BufferMemoryBarrier -> Int -> Ptr BufferMemoryBarrier
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr BufferMemoryBarrier) (BufferMemoryBarrier
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers)
  Ptr (ImageMemoryBarrier Any)
pPImageMemoryBarriers <- ((Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (ImageMemoryBarrier Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (ImageMemoryBarrier Any)))
-> ((Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (ImageMemoryBarrier Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(ImageMemoryBarrier _) ((("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
  (Int -> SomeStruct ImageMemoryBarrier -> ContT () IO ())
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct ImageMemoryBarrier
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct ImageMemoryBarrier)
-> SomeStruct ImageMemoryBarrier -> IO () -> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (ImageMemoryBarrier Any) -> Ptr (SomeStruct ImageMemoryBarrier)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ImageMemoryBarrier Any)
pPImageMemoryBarriers Ptr (ImageMemoryBarrier Any) -> Int -> Ptr (ImageMemoryBarrier _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (ImageMemoryBarrier _))) (SomeStruct ImageMemoryBarrier
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> Ptr Event
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
vkCmdWaitEvents' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("events" ::: Vector Event) -> Int
forall a. Vector a -> Int
Data.Vector.length (("events" ::: Vector Event) -> Int)
-> ("events" ::: Vector Event) -> Int
forall a b. (a -> b) -> a -> b
$ ("events" ::: Vector Event
events)) :: Word32)) (Ptr Event
pPEvents) ("stageMask" ::: PipelineStageFlags
srcStageMask) ("stageMask" ::: PipelineStageFlags
dstStageMask) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("memoryBarriers" ::: Vector MemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length (("memoryBarriers" ::: Vector MemoryBarrier) -> Int)
-> ("memoryBarriers" ::: Vector MemoryBarrier) -> Int
forall a b. (a -> b) -> a -> b
$ ("memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers)) :: Word32)) (Ptr MemoryBarrier
pPMemoryBarriers) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length (("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int
forall a b. (a -> b) -> a -> b
$ ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers)) :: Word32)) (Ptr BufferMemoryBarrier
pPBufferMemoryBarriers) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
 -> Int)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> Int
forall a b. (a -> b) -> a -> b
$ ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers)) :: Word32)) (Ptr (ImageMemoryBarrier Any) -> Ptr (SomeStruct ImageMemoryBarrier)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ImageMemoryBarrier Any)
pPImageMemoryBarriers))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()

-- | vkCmdWaitEvents - Wait for one or more events and insert a set of memory
--
-- = Description
--
-- When 'cmdWaitEvents' is submitted to a queue, it defines a memory
-- dependency between prior event signal operations on the same queue or
-- the host, and subsequent commands. 'cmdWaitEvents' /must/ not be used to
-- wait on event signal operations occurring on other queues.
--
-- The first synchronization scope only includes event signal operations
-- that operate on members of @pEvents@, and the operations that
-- happened-before the event signal operations. Event signal operations
-- performed by 'cmdSetEvent' that occur earlier in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>
-- are included in the first synchronization scope, if the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically latest>
-- pipeline stage in their @stageMask@ parameter is
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically earlier>
-- than or equal to the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically latest>
-- pipeline stage in @srcStageMask@. Event signal operations performed by
-- 'Vulkan.Core10.Event.setEvent' are only included in the first
-- synchronization scope if
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT' is
-- included in @srcStageMask@.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes all commands that occur later in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>.
-- The second synchronization scope is limited to operations on the
-- pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask>
-- specified by @dstStageMask@.
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access in the pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>
-- specified by @srcStageMask@. Within that, the first access scope only
-- includes the first access scopes defined by elements of the
-- @pMemoryBarriers@, @pBufferMemoryBarriers@ and @pImageMemoryBarriers@
-- arrays, which each define a set of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-memory-barriers memory barriers>.
-- If no memory barriers are specified, then the first access scope
-- includes no accesses.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access in the pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask>
-- specified by @dstStageMask@. Within that, the second access scope only
-- includes the second access scopes defined by elements of the
-- @pMemoryBarriers@, @pBufferMemoryBarriers@ and @pImageMemoryBarriers@
-- arrays, which each define a set of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-memory-barriers memory barriers>.
-- If no memory barriers are specified, then the second access scope
-- includes no accesses.
--
-- Note
--
-- 'cmdWaitEvents' is used with 'cmdSetEvent' to define a memory dependency
-- between two sets of action commands, roughly in the same way as pipeline
-- barriers, but split into two commands such that work between the two
-- /may/ execute unhindered.
--
-- Unlike 'cmdPipelineBarrier', a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers queue family ownership transfer>
-- /cannot/ be performed using 'cmdWaitEvents'.
--
-- Note
--
-- Applications /should/ be careful to avoid race conditions when using
-- events. There is no direct ordering guarantee between a 'cmdResetEvent'
-- command and a 'cmdWaitEvents' command submitted after it. Another
-- execution dependency (e.g. a pipeline barrier or semaphore with
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_ALL_COMMANDS_BIT')
-- is needed to prevent such a race condition.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   Any pipeline stage included in @srcStageMask@ /must/ be supported by
--     the capabilities of the queue family specified by the
--     @queueFamilyIndex@ member of the
--     'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' structure that was
--     used to create the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   Any pipeline stage included in @dstStageMask@ /must/ be supported by
--     the capabilities of the queue family specified by the
--     @queueFamilyIndex@ member of the
--     'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' structure that was
--     used to create the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   The @srcAccessMask@ member of each element of @pMemoryBarriers@
--     /must/ only include access flags that are supported by one or more
--     of the pipeline stages in @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   The @dstAccessMask@ member of each element of @pMemoryBarriers@
--     /must/ only include access flags that are supported by one or more
--     of the pipeline stages in @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pBufferMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @srcQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @srcAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pBufferMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @dstQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @dstAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pImageMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @srcQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @srcAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pImageMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @dstQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @dstAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   @srcStageMask@ /must/ be the bitwise OR of the @stageMask@ parameter
--     used in previous calls to 'cmdSetEvent' with any of the members of
--     @pEvents@ and
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT'
--     if any of the members of @pEvents@ was set using
--     'Vulkan.Core10.Event.setEvent'
--
-- -   If @pEvents@ includes one or more events that will be signaled by
--     'Vulkan.Core10.Event.setEvent' after @commandBuffer@ has been
--     submitted to a queue, then 'cmdWaitEvents' /must/ not be called
--     inside a render pass instance
--
-- -   The @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members of any
--     element of @pBufferMemoryBarriers@ or @pImageMemoryBarriers@ /must/
--     be equal
--
-- -   @commandBuffer@’s current device mask /must/ include exactly one
--     physical device
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pEvents@ /must/ be a valid pointer to an array of @eventCount@
--     valid 'Vulkan.Core10.Handles.Event' handles
--
-- -   @srcStageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @srcStageMask@ /must/ not be @0@
--
-- -   @dstStageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @dstStageMask@ /must/ not be @0@
--
-- -   If @memoryBarrierCount@ is not @0@, @pMemoryBarriers@ /must/ be a
--     valid pointer to an array of @memoryBarrierCount@ valid
--     'Vulkan.Core10.OtherTypes.MemoryBarrier' structures
--
-- -   If @bufferMemoryBarrierCount@ is not @0@, @pBufferMemoryBarriers@
--     /must/ be a valid pointer to an array of @bufferMemoryBarrierCount@
--     valid 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures
--
-- -   If @imageMemoryBarrierCount@ is not @0@, @pImageMemoryBarriers@
--     /must/ be a valid pointer to an array of @imageMemoryBarrierCount@
--     valid 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures
--
-- -   @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, or compute operations
--
-- -   @eventCount@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and the elements of @pEvents@ /must/ have
--     been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier',
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Event',
-- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier',
-- 'Vulkan.Core10.OtherTypes.MemoryBarrier',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags'
cmdWaitEvents :: forall io
               . (MonadIO io)
              => -- | @commandBuffer@ is the command buffer into which the command is
                 -- recorded.
                 CommandBuffer
              -> -- | @pEvents@ is a pointer to an array of event object handles to wait on.
                 ("events" ::: Vector Event)
              -> -- | @srcStageMask@ is a bitmask of
                 -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                 -- specifying the
                 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask>.
                 ("srcStageMask" ::: PipelineStageFlags)
              -> -- | @dstStageMask@ is a bitmask of
                 -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                 -- specifying the
                 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages destination stage mask>.
                 ("dstStageMask" ::: PipelineStageFlags)
              -> -- | @pMemoryBarriers@ is a pointer to an array of
                 -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' structures.
                 ("memoryBarriers" ::: Vector MemoryBarrier)
              -> -- | @pBufferMemoryBarriers@ is a pointer to an array of
                 -- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures.
                 ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
              -> -- | @pImageMemoryBarriers@ is a pointer to an array of
                 -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures.
                 ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
              -> io ()
cmdWaitEvents :: CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
cmdWaitEvents = (FunPtr
   (Ptr CommandBuffer_T
    -> ("firstViewport" ::: Word32)
    -> Ptr Event
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("firstViewport" ::: Word32)
    -> Ptr MemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr BufferMemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr (SomeStruct ImageMemoryBarrier)
    -> IO ())
 -> Ptr CommandBuffer_T
 -> ("firstViewport" ::: Word32)
 -> Ptr Event
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("firstViewport" ::: Word32)
 -> Ptr MemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr BufferMemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr (SomeStruct ImageMemoryBarrier)
 -> IO ())
-> CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr CommandBuffer_T
    -> ("firstViewport" ::: Word32)
    -> Ptr Event
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("firstViewport" ::: Word32)
    -> Ptr MemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr BufferMemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr (SomeStruct ImageMemoryBarrier)
    -> IO ())
 -> Ptr CommandBuffer_T
 -> ("firstViewport" ::: Word32)
 -> Ptr Event
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("firstViewport" ::: Word32)
 -> Ptr MemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr BufferMemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr (SomeStruct ImageMemoryBarrier)
 -> IO ())
-> CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
cmdWaitEventsSafeOrUnsafe FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> Ptr Event
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
mkVkCmdWaitEventsUnsafe

-- | A variant of 'cmdWaitEvents' which makes a *safe* FFI call
cmdWaitEventsSafe :: forall io
                   . (MonadIO io)
                  => -- | @commandBuffer@ is the command buffer into which the command is
                     -- recorded.
                     CommandBuffer
                  -> -- | @pEvents@ is a pointer to an array of event object handles to wait on.
                     ("events" ::: Vector Event)
                  -> -- | @srcStageMask@ is a bitmask of
                     -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                     -- specifying the
                     -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask>.
                     ("srcStageMask" ::: PipelineStageFlags)
                  -> -- | @dstStageMask@ is a bitmask of
                     -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                     -- specifying the
                     -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages destination stage mask>.
                     ("dstStageMask" ::: PipelineStageFlags)
                  -> -- | @pMemoryBarriers@ is a pointer to an array of
                     -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' structures.
                     ("memoryBarriers" ::: Vector MemoryBarrier)
                  -> -- | @pBufferMemoryBarriers@ is a pointer to an array of
                     -- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures.
                     ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
                  -> -- | @pImageMemoryBarriers@ is a pointer to an array of
                     -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures.
                     ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
                  -> io ()
cmdWaitEventsSafe :: CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
cmdWaitEventsSafe = (FunPtr
   (Ptr CommandBuffer_T
    -> ("firstViewport" ::: Word32)
    -> Ptr Event
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("firstViewport" ::: Word32)
    -> Ptr MemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr BufferMemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr (SomeStruct ImageMemoryBarrier)
    -> IO ())
 -> Ptr CommandBuffer_T
 -> ("firstViewport" ::: Word32)
 -> Ptr Event
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("firstViewport" ::: Word32)
 -> Ptr MemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr BufferMemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr (SomeStruct ImageMemoryBarrier)
 -> IO ())
-> CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr CommandBuffer_T
    -> ("firstViewport" ::: Word32)
    -> Ptr Event
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("stageMask" ::: PipelineStageFlags)
    -> ("firstViewport" ::: Word32)
    -> Ptr MemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr BufferMemoryBarrier
    -> ("firstViewport" ::: Word32)
    -> Ptr (SomeStruct ImageMemoryBarrier)
    -> IO ())
 -> Ptr CommandBuffer_T
 -> ("firstViewport" ::: Word32)
 -> Ptr Event
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("stageMask" ::: PipelineStageFlags)
 -> ("firstViewport" ::: Word32)
 -> Ptr MemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr BufferMemoryBarrier
 -> ("firstViewport" ::: Word32)
 -> Ptr (SomeStruct ImageMemoryBarrier)
 -> IO ())
-> CommandBuffer
-> ("events" ::: Vector Event)
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
cmdWaitEventsSafeOrUnsafe FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> Ptr Event
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> Ptr Event
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
mkVkCmdWaitEventsSafe


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdPipelineBarrier
  :: FunPtr (Ptr CommandBuffer_T -> PipelineStageFlags -> PipelineStageFlags -> DependencyFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> PipelineStageFlags -> PipelineStageFlags -> DependencyFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr BufferMemoryBarrier -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()

-- | vkCmdPipelineBarrier - Insert a memory dependency
--
-- = Description
--
-- When 'cmdPipelineBarrier' is submitted to a queue, it defines a memory
-- dependency between commands that were submitted before it, and those
-- submitted after it.
--
-- If 'cmdPipelineBarrier' was recorded outside a render pass instance, the
-- first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes all commands that occur earlier in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>.
-- If 'cmdPipelineBarrier' was recorded inside a render pass instance, the
-- first synchronization scope includes only commands that occur earlier in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>
-- within the same subpass. In either case, the first synchronization scope
-- is limited to operations on the pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>
-- specified by @srcStageMask@.
--
-- If 'cmdPipelineBarrier' was recorded outside a render pass instance, the
-- second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>
-- includes all commands that occur later in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>.
-- If 'cmdPipelineBarrier' was recorded inside a render pass instance, the
-- second synchronization scope includes only commands that occur later in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>
-- within the same subpass. In either case, the second synchronization
-- scope is limited to operations on the pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask>
-- specified by @dstStageMask@.
--
-- The first
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access in the pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>
-- specified by @srcStageMask@. Within that, the first access scope only
-- includes the first access scopes defined by elements of the
-- @pMemoryBarriers@, @pBufferMemoryBarriers@ and @pImageMemoryBarriers@
-- arrays, which each define a set of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-memory-barriers memory barriers>.
-- If no memory barriers are specified, then the first access scope
-- includes no accesses.
--
-- The second
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope>
-- is limited to access in the pipeline stages determined by the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask>
-- specified by @dstStageMask@. Within that, the second access scope only
-- includes the second access scopes defined by elements of the
-- @pMemoryBarriers@, @pBufferMemoryBarriers@ and @pImageMemoryBarriers@
-- arrays, which each define a set of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-memory-barriers memory barriers>.
-- If no memory barriers are specified, then the second access scope
-- includes no accesses.
--
-- If @dependencyFlags@ includes
-- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT', then
-- any dependency between
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space>
-- pipeline stages is
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-local>
-- - otherwise it is
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-global>.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   Any pipeline stage included in @srcStageMask@ /must/ be supported by
--     the capabilities of the queue family specified by the
--     @queueFamilyIndex@ member of the
--     'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' structure that was
--     used to create the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   Any pipeline stage included in @dstStageMask@ /must/ be supported by
--     the capabilities of the queue family specified by the
--     @queueFamilyIndex@ member of the
--     'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' structure that was
--     used to create the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   The @srcAccessMask@ member of each element of @pMemoryBarriers@
--     /must/ only include access flags that are supported by one or more
--     of the pipeline stages in @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   The @dstAccessMask@ member of each element of @pMemoryBarriers@
--     /must/ only include access flags that are supported by one or more
--     of the pipeline stages in @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pBufferMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @srcQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @srcAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pBufferMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @dstQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @dstAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pImageMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @srcQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @srcAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   For any element of @pImageMemoryBarriers@, if its
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members are equal,
--     or if its @dstQueueFamilyIndex@ is the queue family index that was
--     used to create the command pool that @commandBuffer@ was allocated
--     from, then its @dstAccessMask@ member /must/ only contain access
--     flags that are supported by one or more of the pipeline stages in
--     @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   If 'cmdPipelineBarrier' is called within a render pass instance, the
--     render pass /must/ have been created with at least one
--     'Vulkan.Core10.Pass.SubpassDependency' instance in
--     'Vulkan.Core10.Pass.RenderPassCreateInfo'::@pDependencies@ that
--     expresses a dependency from the current subpass to itself, with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scopes>
--     and
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scopes>
--     that are all supersets of the scopes defined in this command
--
-- -   If 'cmdPipelineBarrier' is called within a render pass instance, it
--     /must/ not include any buffer memory barriers
--
-- -   If 'cmdPipelineBarrier' is called within a render pass instance, the
--     @image@ member of any image memory barrier included in this command
--     /must/ be an attachment used in the current subpass both as an input
--     attachment, and as either a color or depth\/stencil attachment
--
-- -   If 'cmdPipelineBarrier' is called within a render pass instance, the
--     @oldLayout@ and @newLayout@ members of any image memory barrier
--     included in this command /must/ be equal
--
-- -   If 'cmdPipelineBarrier' is called within a render pass instance, the
--     @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members of any image
--     memory barrier included in this command /must/ be equal
--
-- -   If 'cmdPipelineBarrier' is called outside of a render pass instance,
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT'
--     /must/ not be included in the dependency flags
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @srcStageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @srcStageMask@ /must/ not be @0@
--
-- -   @dstStageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @dstStageMask@ /must/ not be @0@
--
-- -   @dependencyFlags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits' values
--
-- -   If @memoryBarrierCount@ is not @0@, @pMemoryBarriers@ /must/ be a
--     valid pointer to an array of @memoryBarrierCount@ valid
--     'Vulkan.Core10.OtherTypes.MemoryBarrier' structures
--
-- -   If @bufferMemoryBarrierCount@ is not @0@, @pBufferMemoryBarriers@
--     /must/ be a valid pointer to an array of @bufferMemoryBarrierCount@
--     valid 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures
--
-- -   If @imageMemoryBarrierCount@ is not @0@, @pImageMemoryBarriers@
--     /must/ be a valid pointer to an array of @imageMemoryBarrierCount@
--     valid 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures
--
-- -   @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 transfer, graphics, or compute
--     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                                                                                                                   | Transfer                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier',
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlags',
-- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier',
-- 'Vulkan.Core10.OtherTypes.MemoryBarrier',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags'
cmdPipelineBarrier :: forall io
                    . (MonadIO io)
                   => -- | @commandBuffer@ is the command buffer into which the command is
                      -- recorded.
                      CommandBuffer
                   -> -- | @srcStageMask@ is a bitmask of
                      -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                      -- specifying the
                      -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>.
                      ("srcStageMask" ::: PipelineStageFlags)
                   -> -- | @dstStageMask@ is a bitmask of
                      -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
                      -- specifying the
                      -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask>.
                      ("dstStageMask" ::: PipelineStageFlags)
                   -> -- | @dependencyFlags@ is a bitmask of
                      -- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits' specifying
                      -- how execution and memory dependencies are formed.
                      DependencyFlags
                   -> -- | @pMemoryBarriers@ is a pointer to an array of
                      -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' structures.
                      ("memoryBarriers" ::: Vector MemoryBarrier)
                   -> -- | @pBufferMemoryBarriers@ is a pointer to an array of
                      -- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures.
                      ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
                   -> -- | @pImageMemoryBarriers@ is a pointer to an array of
                      -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures.
                      ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
                   -> io ()
cmdPipelineBarrier :: CommandBuffer
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> DependencyFlags
-> ("memoryBarriers" ::: Vector MemoryBarrier)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> io ()
cmdPipelineBarrier commandBuffer :: CommandBuffer
commandBuffer srcStageMask :: "stageMask" ::: PipelineStageFlags
srcStageMask dstStageMask :: "stageMask" ::: PipelineStageFlags
dstStageMask dependencyFlags :: DependencyFlags
dependencyFlags memoryBarriers :: "memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers bufferMemoryBarriers :: "bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers imageMemoryBarriers :: "imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdPipelineBarrierPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> DependencyFlags
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
vkCmdPipelineBarrierPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("stageMask" ::: PipelineStageFlags)
      -> ("stageMask" ::: PipelineStageFlags)
      -> DependencyFlags
      -> ("firstViewport" ::: Word32)
      -> Ptr MemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr BufferMemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr (SomeStruct ImageMemoryBarrier)
      -> IO ())
pVkCmdPipelineBarrier (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> DependencyFlags
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
vkCmdPipelineBarrierPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> DependencyFlags
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("stageMask" ::: PipelineStageFlags)
      -> ("stageMask" ::: PipelineStageFlags)
      -> DependencyFlags
      -> ("firstViewport" ::: Word32)
      -> Ptr MemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr BufferMemoryBarrier
      -> ("firstViewport" ::: Word32)
      -> Ptr (SomeStruct ImageMemoryBarrier)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> DependencyFlags
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> 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 vkCmdPipelineBarrier is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdPipelineBarrier' :: Ptr CommandBuffer_T
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> DependencyFlags
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
vkCmdPipelineBarrier' = FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> DependencyFlags
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> DependencyFlags
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
mkVkCmdPipelineBarrier FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> ("stageMask" ::: PipelineStageFlags)
   -> DependencyFlags
   -> ("firstViewport" ::: Word32)
   -> Ptr MemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr BufferMemoryBarrier
   -> ("firstViewport" ::: Word32)
   -> Ptr (SomeStruct ImageMemoryBarrier)
   -> IO ())
vkCmdPipelineBarrierPtr
  Ptr MemoryBarrier
pPMemoryBarriers <- ((Ptr MemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr MemoryBarrier)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MemoryBarrier -> IO ()) -> IO ())
 -> ContT () IO (Ptr MemoryBarrier))
-> ((Ptr MemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr MemoryBarrier)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr MemoryBarrier -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @MemoryBarrier ((("memoryBarriers" ::: Vector MemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length ("memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
  (Int -> MemoryBarrier -> ContT () IO ())
-> ("memoryBarriers" ::: Vector MemoryBarrier) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MemoryBarrier
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr MemoryBarrier -> MemoryBarrier -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr MemoryBarrier
pPMemoryBarriers Ptr MemoryBarrier -> Int -> Ptr MemoryBarrier
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryBarrier) (MemoryBarrier
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers)
  Ptr BufferMemoryBarrier
pPBufferMemoryBarriers <- ((Ptr BufferMemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr BufferMemoryBarrier)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr BufferMemoryBarrier -> IO ()) -> IO ())
 -> ContT () IO (Ptr BufferMemoryBarrier))
-> ((Ptr BufferMemoryBarrier -> IO ()) -> IO ())
-> ContT () IO (Ptr BufferMemoryBarrier)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr BufferMemoryBarrier -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @BufferMemoryBarrier ((("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
  (Int -> BufferMemoryBarrier -> ContT () IO ())
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier)
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: BufferMemoryBarrier
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr BufferMemoryBarrier
pPBufferMemoryBarriers Ptr BufferMemoryBarrier -> Int -> Ptr BufferMemoryBarrier
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr BufferMemoryBarrier) (BufferMemoryBarrier
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers)
  Ptr (ImageMemoryBarrier Any)
pPImageMemoryBarriers <- ((Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (ImageMemoryBarrier Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (ImageMemoryBarrier Any)))
-> ((Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (ImageMemoryBarrier Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (ImageMemoryBarrier Any) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(ImageMemoryBarrier _) ((("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
  (Int -> SomeStruct ImageMemoryBarrier -> ContT () IO ())
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct ImageMemoryBarrier
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct ImageMemoryBarrier)
-> SomeStruct ImageMemoryBarrier -> IO () -> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (ImageMemoryBarrier Any) -> Ptr (SomeStruct ImageMemoryBarrier)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ImageMemoryBarrier Any)
pPImageMemoryBarriers Ptr (ImageMemoryBarrier Any) -> Int -> Ptr (ImageMemoryBarrier _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (ImageMemoryBarrier _))) (SomeStruct ImageMemoryBarrier
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("stageMask" ::: PipelineStageFlags)
-> ("stageMask" ::: PipelineStageFlags)
-> DependencyFlags
-> ("firstViewport" ::: Word32)
-> Ptr MemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr BufferMemoryBarrier
-> ("firstViewport" ::: Word32)
-> Ptr (SomeStruct ImageMemoryBarrier)
-> IO ()
vkCmdPipelineBarrier' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("stageMask" ::: PipelineStageFlags
srcStageMask) ("stageMask" ::: PipelineStageFlags
dstStageMask) (DependencyFlags
dependencyFlags) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("memoryBarriers" ::: Vector MemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length (("memoryBarriers" ::: Vector MemoryBarrier) -> Int)
-> ("memoryBarriers" ::: Vector MemoryBarrier) -> Int
forall a b. (a -> b) -> a -> b
$ ("memoryBarriers" ::: Vector MemoryBarrier
memoryBarriers)) :: Word32)) (Ptr MemoryBarrier
pPMemoryBarriers) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int
forall a. Vector a -> Int
Data.Vector.length (("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int)
-> ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier) -> Int
forall a b. (a -> b) -> a -> b
$ ("bufferMemoryBarriers" ::: Vector BufferMemoryBarrier
bufferMemoryBarriers)) :: Word32)) (Ptr BufferMemoryBarrier
pPBufferMemoryBarriers) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier))
 -> Int)
-> ("imageMemoryBarriers"
    ::: Vector (SomeStruct ImageMemoryBarrier))
-> Int
forall a b. (a -> b) -> a -> b
$ ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)
imageMemoryBarriers)) :: Word32)) (Ptr (ImageMemoryBarrier Any) -> Ptr (SomeStruct ImageMemoryBarrier)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ImageMemoryBarrier Any)
pPImageMemoryBarriers))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdBeginQuery - Begin a query
--
-- = Description
--
-- If the @queryType@ of the pool is
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' and @flags@
-- contains
-- 'Vulkan.Core10.Enums.QueryControlFlagBits.QUERY_CONTROL_PRECISE_BIT', an
-- implementation /must/ return a result that matches the actual number of
-- samples passed. This is described in more detail in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-occlusion Occlusion Queries>.
--
-- Calling 'cmdBeginQuery' is equivalent to calling
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginQueryIndexedEXT'
-- with the @index@ parameter set to zero.
--
-- After beginning a query, that query is considered /active/ within the
-- command buffer it was called in until that same query is ended. Queries
-- active in a primary command buffer when secondary command buffers are
-- executed are considered active for those secondary command buffers.
--
-- == Valid Usage
--
-- -   @queryPool@ /must/ have been created with a @queryType@ that differs
--     from that of any queries that are
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>
--     within @commandBuffer@
--
-- -   All queries used by the command /must/ be unavailable
--
-- -   The @queryType@ used to create @queryPool@ /must/ not be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-occlusionQueryPrecise precise occlusion queries>
--     feature is not enabled, or the @queryType@ used to create
--     @queryPool@ was not
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION', @flags@ /must/
--     not contain
--     'Vulkan.Core10.Enums.QueryControlFlagBits.QUERY_CONTROL_PRECISE_BIT'
--
-- -   @query@ /must/ be less than the number of queries in @queryPool@
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION', the
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS' and
--     any of the @pipelineStatistics@ indicate graphics operations, the
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS' and
--     any of the @pipelineStatistics@ indicate compute operations, the
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   @commandBuffer@ /must/ not be a protected command buffer
--
-- -   If called within a render pass instance, the sum of @query@ and the
--     number of bits set in the current subpass’s view mask /must/ be less
--     than or equal to the number of queries in @queryPool@
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT'
--     the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT'
--     then
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PhysicalDeviceTransformFeedbackPropertiesEXT'::@transformFeedbackQueries@
--     /must/ be supported
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#profiling-lock profiling lock>
--     /must/ have been held before
--     'Vulkan.Core10.CommandBuffer.beginCommandBuffer' was called on
--     @commandBuffer@
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' and
--     one of the counters used to create @queryPool@ was
--     'Vulkan.Extensions.VK_KHR_performance_query.PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR',
--     the query begin /must/ be the first recorded command in
--     @commandBuffer@
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' and
--     one of the counters used to create @queryPool@ was
--     'Vulkan.Extensions.VK_KHR_performance_query.PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR',
--     the begin command /must/ not be recorded within a render pass
--     instance
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' and
--     another query pool with a @queryType@
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' has
--     been used within @commandBuffer@, its parent primary command buffer
--     or secondary command buffer recorded within the same parent primary
--     command buffer as @commandBuffer@, the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-performanceCounterMultipleQueryPools performanceCounterMultipleQueryPools>
--     feature /must/ be enabled
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     this command /must/ not be recorded in a command buffer that, either
--     directly or through secondary command buffers, also contains a
--     'cmdResetQueryPool' command affecting the same query
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     handle
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.QueryControlFlagBits.QueryControlFlagBits'
--     values
--
-- -   @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, or compute operations
--
-- -   Both of @commandBuffer@, and @queryPool@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.QueryControlFlagBits.QueryControlFlags',
-- 'Vulkan.Core10.Handles.QueryPool'
cmdBeginQuery :: forall io
               . (MonadIO io)
              => -- | @commandBuffer@ is the command buffer into which this command will be
                 -- recorded.
                 CommandBuffer
              -> -- | @queryPool@ is the query pool that will manage the results of the query.
                 QueryPool
              -> -- | @query@ is the query index within the query pool that will contain the
                 -- results.
                 ("query" ::: Word32)
              -> -- | @flags@ is a bitmask of
                 -- 'Vulkan.Core10.Enums.QueryControlFlagBits.QueryControlFlagBits'
                 -- specifying constraints on the types of queries that /can/ be performed.
                 QueryControlFlags
              -> io ()
cmdBeginQuery :: CommandBuffer
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> io ()
cmdBeginQuery commandBuffer :: CommandBuffer
commandBuffer queryPool :: QueryPool
queryPool query :: "firstViewport" ::: Word32
query flags :: QueryControlFlags
flags = 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 vkCmdBeginQueryPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> QueryControlFlags
   -> IO ())
vkCmdBeginQueryPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> QueryControlFlags
      -> IO ())
pVkCmdBeginQuery (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> QueryControlFlags
   -> IO ())
vkCmdBeginQueryPtr FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> QueryControlFlags
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> QueryControlFlags
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> QueryControlFlags
   -> 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 vkCmdBeginQuery is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBeginQuery' :: Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> IO ()
vkCmdBeginQuery' = FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> QueryControlFlags
   -> IO ())
-> Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> IO ()
mkVkCmdBeginQuery FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> QueryControlFlags
   -> IO ())
vkCmdBeginQueryPtr
  Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> IO ()
vkCmdBeginQuery' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (QueryPool
queryPool) ("firstViewport" ::: Word32
query) (QueryControlFlags
flags)
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()

-- | This function will call the supplied action between calls to
-- 'cmdBeginQuery' and 'cmdEndQuery'
--
-- Note that 'cmdEndQuery' is *not* called if an exception is thrown by the
-- inner action.
cmdUseQuery :: forall io r . MonadIO io => CommandBuffer -> QueryPool -> Word32 -> QueryControlFlags -> io r -> io r
cmdUseQuery :: CommandBuffer
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> io r
-> io r
cmdUseQuery commandBuffer :: CommandBuffer
commandBuffer queryPool :: QueryPool
queryPool query :: "firstViewport" ::: Word32
query flags :: QueryControlFlags
flags a :: io r
a =
  (CommandBuffer
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> io ()
forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> QueryPool
-> ("firstViewport" ::: Word32)
-> QueryControlFlags
-> io ()
cmdBeginQuery CommandBuffer
commandBuffer QueryPool
queryPool "firstViewport" ::: Word32
query QueryControlFlags
flags) io () -> io r -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a io r -> io () -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> io ()
forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> io ()
cmdEndQuery CommandBuffer
commandBuffer QueryPool
queryPool "firstViewport" ::: Word32
query)


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

-- | vkCmdEndQuery - Ends a query
--
-- = Description
--
-- Calling 'cmdEndQuery' is equivalent to calling
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT' with
-- the @index@ parameter set to zero.
--
-- As queries operate asynchronously, ending a query does not immediately
-- set the query’s status to available. A query is considered /finished/
-- when the final results of the query are ready to be retrieved by
-- 'Vulkan.Core10.Query.getQueryPoolResults' and 'cmdCopyQueryPoolResults',
-- and this is when the query’s status is set to available.
--
-- Once a query is ended the query /must/ finish in finite time, unless the
-- state of the query is changed using other commands, e.g. by issuing a
-- reset of the query.
--
-- == Valid Usage
--
-- -   All queries used by the command /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>
--
-- -   @query@ /must/ be less than the number of queries in @queryPool@
--
-- -   @commandBuffer@ /must/ not be a protected command buffer
--
-- -   If 'cmdEndQuery' is called within a render pass instance, the sum of
--     @query@ and the number of bits set in the current subpass’s view
--     mask /must/ be less than or equal to the number of queries in
--     @queryPool@
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' and
--     one or more of the counters used to create @queryPool@ was
--     'Vulkan.Extensions.VK_KHR_performance_query.PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR',
--     the 'cmdEndQuery' /must/ be the last recorded command in
--     @commandBuffer@
--
-- -   If @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' and
--     one or more of the counters used to create @queryPool@ was
--     'Vulkan.Extensions.VK_KHR_performance_query.PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR',
--     the 'cmdEndQuery' /must/ not be recorded within a render pass
--     instance
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     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, or compute operations
--
-- -   Both of @commandBuffer@, and @queryPool@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.QueryPool'
cmdEndQuery :: forall io
             . (MonadIO io)
            => -- | @commandBuffer@ is the command buffer into which this command will be
               -- recorded.
               CommandBuffer
            -> -- | @queryPool@ is the query pool that is managing the results of the query.
               QueryPool
            -> -- | @query@ is the query index within the query pool where the result is
               -- stored.
               ("query" ::: Word32)
            -> io ()
cmdEndQuery :: CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> io ()
cmdEndQuery commandBuffer :: CommandBuffer
commandBuffer queryPool :: QueryPool
queryPool query :: "firstViewport" ::: Word32
query = 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 vkCmdEndQueryPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
vkCmdEndQueryPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
pVkCmdEndQuery (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
vkCmdEndQueryPtr FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool -> ("firstViewport" ::: 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 vkCmdEndQuery is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdEndQuery' :: Ptr CommandBuffer_T
-> QueryPool -> ("firstViewport" ::: Word32) -> IO ()
vkCmdEndQuery' = FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
-> Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdEndQuery FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool -> ("firstViewport" ::: Word32) -> IO ())
vkCmdEndQueryPtr
  Ptr CommandBuffer_T
-> QueryPool -> ("firstViewport" ::: Word32) -> IO ()
vkCmdEndQuery' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (QueryPool
queryPool) ("firstViewport" ::: Word32
query)
  () -> 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" mkVkCmdResetQueryPool
  :: FunPtr (Ptr CommandBuffer_T -> QueryPool -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> QueryPool -> Word32 -> Word32 -> IO ()

-- | vkCmdResetQueryPool - Reset queries in a query pool
--
-- = Description
--
-- When executed on a queue, this command sets the status of query indices
-- [@firstQuery@, @firstQuery@ + @queryCount@ - 1] to unavailable.
--
-- If the @queryType@ used to create @queryPool@ was
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR', this
-- command sets the status of query indices [@firstQuery@, @firstQuery@ +
-- @queryCount@ - 1] to unavailable for each pass of @queryPool@, as
-- indicated by a call to
-- 'Vulkan.Extensions.VK_KHR_performance_query.getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR'.
--
-- Note
--
-- Because 'cmdResetQueryPool' resets all the passes of the indicated
-- queries, applications must not record a 'cmdResetQueryPool' command for
-- a @queryPool@ created with
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR' in a
-- command buffer that needs to be submitted multiple times as indicated by
-- a call to
-- 'Vulkan.Extensions.VK_KHR_performance_query.getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR'.
-- Otherwise applications will never be able to complete the recorded
-- queries.
--
-- == Valid Usage
--
-- -   @firstQuery@ /must/ be less than the number of queries in
--     @queryPool@
--
-- -   The sum of @firstQuery@ and @queryCount@ /must/ be less than or
--     equal to the number of queries in @queryPool@
--
-- -   All queries used by the command /must/ not be active
--
-- -   If @queryPool@ was created with
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     this command /must/ not be recorded in a command buffer that, either
--     directly or through secondary command buffers, also contains begin
--     commands for a query from the set of queries [@firstQuery@,
--     @firstQuery@ + @queryCount@ - 1]
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     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, or compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Both of @commandBuffer@, and @queryPool@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.QueryPool'
cmdResetQueryPool :: forall io
                   . (MonadIO io)
                  => -- | @commandBuffer@ is the command buffer into which this command will be
                     -- recorded.
                     CommandBuffer
                  -> -- | @queryPool@ is the handle of the query pool managing the queries being
                     -- reset.
                     QueryPool
                  -> -- | @firstQuery@ is the initial query index to reset.
                     ("firstQuery" ::: Word32)
                  -> -- | @queryCount@ is the number of queries to reset.
                     ("queryCount" ::: Word32)
                  -> io ()
cmdResetQueryPool :: CommandBuffer
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> io ()
cmdResetQueryPool commandBuffer :: CommandBuffer
commandBuffer queryPool :: QueryPool
queryPool firstQuery :: "firstViewport" ::: Word32
firstQuery queryCount :: "firstViewport" ::: Word32
queryCount = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdResetQueryPoolPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdResetQueryPoolPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdResetQueryPool (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdResetQueryPoolPtr FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: 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 vkCmdResetQueryPool is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdResetQueryPool' :: Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdResetQueryPool' = FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdResetQueryPool FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdResetQueryPoolPtr
  Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdResetQueryPool' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (QueryPool
queryPool) ("firstViewport" ::: Word32
firstQuery) ("firstViewport" ::: Word32
queryCount)
  () -> 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" mkVkCmdWriteTimestamp
  :: FunPtr (Ptr CommandBuffer_T -> PipelineStageFlagBits -> QueryPool -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> PipelineStageFlagBits -> QueryPool -> Word32 -> IO ()

-- | vkCmdWriteTimestamp - Write a device timestamp into a query object
--
-- = Description
--
-- 'cmdWriteTimestamp' latches the value of the timer when all previous
-- commands have completed executing as far as the specified pipeline
-- stage, and writes the timestamp value to memory. When the timestamp
-- value is written, the availability status of the query is set to
-- available.
--
-- Note
--
-- If an implementation is unable to detect completion and latch the timer
-- at any specific stage of the pipeline, it /may/ instead do so at any
-- logically later stage.
--
-- Timestamps /may/ only be meaningfully compared if they are written by
-- commands submitted to the same queue.
--
-- Note
--
-- An example of such a comparison is determining the execution time of a
-- sequence of commands.
--
-- If 'cmdWriteTimestamp' is called while executing a render pass instance
-- that has multiview enabled, the timestamp uses N consecutive query
-- indices in the query pool (starting at @query@) where N is the number of
-- bits set in the view mask of the subpass the command is executed in. The
-- resulting query values are determined by an implementation-dependent
-- choice of one of the following behaviors:
--
-- -   The first query is a timestamp value and (if more than one bit is
--     set in the view mask) zero is written to the remaining queries. If
--     two timestamps are written in the same subpass, the sum of the
--     execution time of all views between those commands is the difference
--     between the first query written by each command.
--
-- -   All N queries are timestamp values. If two timestamps are written in
--     the same subpass, the sum of the execution time of all views between
--     those commands is the sum of the difference between corresponding
--     queries written by each command. The difference between
--     corresponding queries /may/ be the execution time of a single view.
--
-- In either case, the application /can/ sum the differences between all N
-- queries to determine the total execution time.
--
-- == Valid Usage
--
-- -   @pipelineStage@ /must/ be a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported valid stage>
--     for the queue family that was used to create the command pool that
--     @commandBuffer@ was allocated from
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditional rendering>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragment density map>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transform feedback>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shading rate image>
--     feature is not enabled, @pipelineStage@ /must/ not be
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_SHADING_RATE_IMAGE_BIT_NV'
--
-- -   @queryPool@ /must/ have been created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP'
--
-- -   The query identified by @queryPool@ and @query@ /must/ be
--     /unavailable/
--
-- -   The command pool’s queue family /must/ support a non-zero
--     @timestampValidBits@
--
-- -   All queries used by the command /must/ be unavailable
--
-- -   If 'cmdWriteTimestamp' is called within a render pass instance, the
--     sum of @query@ and the number of bits set in the current subpass’s
--     view mask /must/ be less than or equal to the number of queries in
--     @queryPool@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pipelineStage@ /must/ be a valid
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     value
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     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 transfer, graphics, or compute
--     operations
--
-- -   Both of @commandBuffer@, and @queryPool@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                   | Transfer                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits',
-- 'Vulkan.Core10.Handles.QueryPool'
cmdWriteTimestamp :: forall io
                   . (MonadIO io)
                  => -- | @commandBuffer@ is the command buffer into which the command will be
                     -- recorded.
                     CommandBuffer
                  -> -- | @pipelineStage@ is one of the
                     -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits',
                     -- specifying a stage of the pipeline.
                     PipelineStageFlagBits
                  -> -- | @queryPool@ is the query pool that will manage the timestamp.
                     QueryPool
                  -> -- | @query@ is the query within the query pool that will contain the
                     -- timestamp.
                     ("query" ::: Word32)
                  -> io ()
cmdWriteTimestamp :: CommandBuffer
-> ("stageMask" ::: PipelineStageFlags)
-> QueryPool
-> ("firstViewport" ::: Word32)
-> io ()
cmdWriteTimestamp commandBuffer :: CommandBuffer
commandBuffer pipelineStage :: "stageMask" ::: PipelineStageFlags
pipelineStage queryPool :: QueryPool
queryPool query :: "firstViewport" ::: Word32
query = 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 vkCmdWriteTimestampPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdWriteTimestampPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("stageMask" ::: PipelineStageFlags)
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> IO ())
pVkCmdWriteTimestamp (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdWriteTimestampPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("stageMask" ::: PipelineStageFlags)
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> QueryPool
   -> ("firstViewport" ::: 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 vkCmdWriteTimestamp is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdWriteTimestamp' :: Ptr CommandBuffer_T
-> ("stageMask" ::: PipelineStageFlags)
-> QueryPool
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdWriteTimestamp' = FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("stageMask" ::: PipelineStageFlags)
-> QueryPool
-> ("firstViewport" ::: Word32)
-> IO ()
mkVkCmdWriteTimestamp FunPtr
  (Ptr CommandBuffer_T
   -> ("stageMask" ::: PipelineStageFlags)
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> IO ())
vkCmdWriteTimestampPtr
  Ptr CommandBuffer_T
-> ("stageMask" ::: PipelineStageFlags)
-> QueryPool
-> ("firstViewport" ::: Word32)
-> IO ()
vkCmdWriteTimestamp' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("stageMask" ::: PipelineStageFlags
pipelineStage) (QueryPool
queryPool) ("firstViewport" ::: Word32
query)
  () -> 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" mkVkCmdCopyQueryPoolResults
  :: FunPtr (Ptr CommandBuffer_T -> QueryPool -> Word32 -> Word32 -> Buffer -> DeviceSize -> DeviceSize -> QueryResultFlags -> IO ()) -> Ptr CommandBuffer_T -> QueryPool -> Word32 -> Word32 -> Buffer -> DeviceSize -> DeviceSize -> QueryResultFlags -> IO ()

-- | vkCmdCopyQueryPoolResults - Copy the results of queries in a query pool
-- to a buffer object
--
-- = Description
--
-- 'cmdCopyQueryPoolResults' is guaranteed to see the effect of previous
-- uses of 'cmdResetQueryPool' in the same queue, without any additional
-- synchronization. Thus, the results will always reflect the most recent
-- use of the query.
--
-- @flags@ has the same possible values described above for the @flags@
-- parameter of 'Vulkan.Core10.Query.getQueryPoolResults', but the
-- different style of execution causes some subtle behavioral differences.
-- Because 'cmdCopyQueryPoolResults' executes in order with respect to
-- other query commands, there is less ambiguity about which use of a query
-- is being requested.
--
-- Results for all requested occlusion queries, pipeline statistics
-- queries, transform feedback queries, and timestamp queries are written
-- as 64-bit unsigned integer values if
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set or
-- 32-bit unsigned integer values otherwise. Performance queries store
-- results in a tightly packed array whose type is determined by the @unit@
-- member of the corresponding
-- 'Vulkan.Extensions.VK_KHR_performance_query.PerformanceCounterKHR'.
--
-- If neither of
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' and
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
-- are set, results are only written out for queries in the available
-- state.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' is
-- set, the implementation will wait for each query’s status to be in the
-- available state before retrieving the numerical results for that query.
-- This is guaranteed to reflect the most recent use of the query on the
-- same queue, assuming that the query is not being simultaneously used by
-- other queues. If the query does not become available in a finite amount
-- of time (e.g. due to not issuing a query since the last reset), a
-- 'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST' error /may/ occur.
--
-- Similarly, if
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT'
-- is set and
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' is not
-- set, the availability is guaranteed to reflect the most recent use of
-- the query on the same queue, assuming that the query is not being
-- simultaneously used by other queues. As with
-- 'Vulkan.Core10.Query.getQueryPoolResults', implementations /must/
-- guarantee that if they return a non-zero availability value, then the
-- numerical results are valid.
--
-- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT' is
-- set, 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT' is
-- not set, and the query’s status is unavailable, an intermediate result
-- value between zero and the final result value is written for that query.
--
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT'
-- /must/ not be used if the pool’s @queryType@ is
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP'.
--
-- 'cmdCopyQueryPoolResults' is considered to be a transfer operation, and
-- its writes to buffer memory /must/ be synchronized using
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFER_BIT'
-- and 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_TRANSFER_WRITE_BIT'
-- before using the results.
--
-- == Valid Usage
--
-- -   @dstOffset@ /must/ be less than the size of @dstBuffer@
--
-- -   @firstQuery@ /must/ be less than the number of queries in
--     @queryPool@
--
-- -   The sum of @firstQuery@ and @queryCount@ /must/ be less than or
--     equal to the number of queries in @queryPool@
--
-- -   If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is
--     not set in @flags@ then @dstOffset@ and @stride@ /must/ be multiples
--     of @4@
--
-- -   If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is
--     set in @flags@ then @dstOffset@ and @stride@ /must/ be multiples of
--     @8@
--
-- -   @dstBuffer@ /must/ have enough storage, from @dstOffset@, to contain
--     the result of each query, as described
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-memorylayout here>
--
-- -   @dstBuffer@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT'
--     usage flag
--
-- -   If @dstBuffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP', @flags@ /must/
--     not contain
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT'
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     'Vulkan.Extensions.VK_KHR_performance_query.PhysicalDevicePerformanceQueryPropertiesKHR'::@allowCommandBufferQueryCopies@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     @flags@ /must/ not contain
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT',
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT'
--     or 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT'
--
-- -   If the @queryType@ used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     the @queryPool@ /must/ have been submitted once for each pass as
--     retrieved via a call to
--     'Vulkan.Extensions.VK_KHR_performance_query.getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR'
--
-- -   'cmdCopyQueryPoolResults' /must/ not be called if the @queryType@
--     used to create @queryPool@ was
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_INTEL'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     handle
--
-- -   @dstBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlagBits' values
--
-- -   @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, or compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Each of @commandBuffer@, @dstBuffer@, and @queryPool@ /must/ have
--     been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                | Graphics                                                                                                              | Transfer                                                                                                                            |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Handles.QueryPool',
-- 'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlags'
cmdCopyQueryPoolResults :: forall io
                         . (MonadIO io)
                        => -- | @commandBuffer@ is the command buffer into which this command will be
                           -- recorded.
                           CommandBuffer
                        -> -- | @queryPool@ is the query pool managing the queries containing the
                           -- desired results.
                           QueryPool
                        -> -- | @firstQuery@ is the initial query index.
                           ("firstQuery" ::: Word32)
                        -> -- | @queryCount@ is the number of queries. @firstQuery@ and @queryCount@
                           -- together define a range of queries.
                           ("queryCount" ::: Word32)
                        -> -- | @dstBuffer@ is a 'Vulkan.Core10.Handles.Buffer' object that will receive
                           -- the results of the copy command.
                           ("dstBuffer" ::: Buffer)
                        -> -- | @dstOffset@ is an offset into @dstBuffer@.
                           ("dstOffset" ::: DeviceSize)
                        -> -- | @stride@ is the stride in bytes between results for individual queries
                           -- within @dstBuffer@. The required size of the backing memory for
                           -- @dstBuffer@ is determined as described above for
                           -- 'Vulkan.Core10.Query.getQueryPoolResults'.
                           ("stride" ::: DeviceSize)
                        -> -- | @flags@ is a bitmask of
                           -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlagBits' specifying
                           -- how and when results are returned.
                           QueryResultFlags
                        -> io ()
cmdCopyQueryPoolResults :: CommandBuffer
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> QueryResultFlags
-> io ()
cmdCopyQueryPoolResults commandBuffer :: CommandBuffer
commandBuffer queryPool :: QueryPool
queryPool firstQuery :: "firstViewport" ::: Word32
firstQuery queryCount :: "firstViewport" ::: Word32
queryCount dstBuffer :: Buffer
dstBuffer dstOffset :: "offset" ::: DeviceSize
dstOffset stride :: "offset" ::: DeviceSize
stride flags :: QueryResultFlags
flags = 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 vkCmdCopyQueryPoolResultsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> QueryResultFlags
   -> IO ())
vkCmdCopyQueryPoolResultsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("offset" ::: DeviceSize)
      -> QueryResultFlags
      -> IO ())
pVkCmdCopyQueryPoolResults (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> QueryResultFlags
   -> IO ())
vkCmdCopyQueryPoolResultsPtr FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> QueryResultFlags
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> QueryPool
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("offset" ::: DeviceSize)
      -> QueryResultFlags
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> QueryResultFlags
   -> 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 vkCmdCopyQueryPoolResults is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyQueryPoolResults' :: Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> QueryResultFlags
-> IO ()
vkCmdCopyQueryPoolResults' = FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> QueryResultFlags
   -> IO ())
-> Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> QueryResultFlags
-> IO ()
mkVkCmdCopyQueryPoolResults FunPtr
  (Ptr CommandBuffer_T
   -> QueryPool
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("offset" ::: DeviceSize)
   -> QueryResultFlags
   -> IO ())
vkCmdCopyQueryPoolResultsPtr
  Ptr CommandBuffer_T
-> QueryPool
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> QueryResultFlags
-> IO ()
vkCmdCopyQueryPoolResults' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (QueryPool
queryPool) ("firstViewport" ::: Word32
firstQuery) ("firstViewport" ::: Word32
queryCount) (Buffer
dstBuffer) ("offset" ::: DeviceSize
dstOffset) ("offset" ::: DeviceSize
stride) (QueryResultFlags
flags)
  () -> 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" mkVkCmdPushConstants
  :: FunPtr (Ptr CommandBuffer_T -> PipelineLayout -> ShaderStageFlags -> Word32 -> Word32 -> Ptr () -> IO ()) -> Ptr CommandBuffer_T -> PipelineLayout -> ShaderStageFlags -> Word32 -> Word32 -> Ptr () -> IO ()

-- | vkCmdPushConstants - Update the values of push constants
--
-- = Description
--
-- Note
--
-- As @stageFlags@ needs to include all flags the relevant push constant
-- ranges were created with, any flags that are not supported by the queue
-- family that the 'Vulkan.Core10.Handles.CommandPool' used to allocate
-- @commandBuffer@ was created on are ignored.
--
-- == Valid Usage
--
-- -   For each byte in the range specified by @offset@ and @size@ and for
--     each shader stage in @stageFlags@, there /must/ be a push constant
--     range in @layout@ that includes that byte and that stage
--
-- -   For each byte in the range specified by @offset@ and @size@ and for
--     each push constant range that overlaps that byte, @stageFlags@
--     /must/ include all stages in that push constant range’s
--     'Vulkan.Core10.PipelineLayout.PushConstantRange'::@stageFlags@
--
-- -   @offset@ /must/ be a multiple of @4@
--
-- -   @size@ /must/ be a multiple of @4@
--
-- -   @offset@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@
--
-- -   @size@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@
--     minus @offset@
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     handle
--
-- -   @stageFlags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' values
--
-- -   @stageFlags@ /must/ not be @0@
--
-- -   @pValues@ /must/ be a valid pointer to an array of @size@ bytes
--
-- -   @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, or compute operations
--
-- -   @size@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and @layout@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Handles.PipelineLayout',
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlags'
cmdPushConstants :: forall io
                  . (MonadIO io)
                 => -- | @commandBuffer@ is the command buffer in which the push constant update
                    -- will be recorded.
                    CommandBuffer
                 -> -- | @layout@ is the pipeline layout used to program the push constant
                    -- updates.
                    PipelineLayout
                 -> -- | @stageFlags@ is a bitmask of
                    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' specifying
                    -- the shader stages that will use the push constants in the updated range.
                    ShaderStageFlags
                 -> -- | @offset@ is the start offset of the push constant range to update, in
                    -- units of bytes.
                    ("offset" ::: Word32)
                 -> -- | @size@ is the size of the push constant range to update, in units of
                    -- bytes.
                    ("size" ::: Word32)
                 -> -- | @pValues@ is a pointer to an array of @size@ bytes containing the new
                    -- push constant values.
                    ("values" ::: Ptr ())
                 -> io ()
cmdPushConstants :: CommandBuffer
-> PipelineLayout
-> ShaderStageFlags
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("data" ::: Ptr ())
-> io ()
cmdPushConstants commandBuffer :: CommandBuffer
commandBuffer layout :: PipelineLayout
layout stageFlags :: ShaderStageFlags
stageFlags offset :: "firstViewport" ::: Word32
offset size :: "firstViewport" ::: Word32
size values :: "data" ::: Ptr ()
values = 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 vkCmdPushConstantsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> PipelineLayout
   -> ShaderStageFlags
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdPushConstantsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> PipelineLayout
      -> ShaderStageFlags
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("data" ::: Ptr ())
      -> IO ())
pVkCmdPushConstants (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> PipelineLayout
   -> ShaderStageFlags
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdPushConstantsPtr FunPtr
  (Ptr CommandBuffer_T
   -> PipelineLayout
   -> ShaderStageFlags
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> PipelineLayout
      -> ShaderStageFlags
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("data" ::: Ptr ())
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> PipelineLayout
   -> ShaderStageFlags
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("data" ::: Ptr ())
   -> 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 vkCmdPushConstants is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdPushConstants' :: Ptr CommandBuffer_T
-> PipelineLayout
-> ShaderStageFlags
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdPushConstants' = FunPtr
  (Ptr CommandBuffer_T
   -> PipelineLayout
   -> ShaderStageFlags
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
-> Ptr CommandBuffer_T
-> PipelineLayout
-> ShaderStageFlags
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
mkVkCmdPushConstants FunPtr
  (Ptr CommandBuffer_T
   -> PipelineLayout
   -> ShaderStageFlags
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdPushConstantsPtr
  Ptr CommandBuffer_T
-> PipelineLayout
-> ShaderStageFlags
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdPushConstants' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (PipelineLayout
layout) (ShaderStageFlags
stageFlags) ("firstViewport" ::: Word32
offset) ("firstViewport" ::: Word32
size) ("data" ::: Ptr ()
values)
  () -> 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" mkVkCmdBeginRenderPass
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct RenderPassBeginInfo) -> SubpassContents -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct RenderPassBeginInfo) -> SubpassContents -> IO ()

-- | vkCmdBeginRenderPass - Begin a new render pass
--
-- = Description
--
-- After beginning a render pass instance, the command buffer is ready to
-- record the commands for the first subpass of that render pass.
--
-- == Valid Usage
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If any of the @stencilInitialLayout@ or @stencilFinalLayout@ member
--     of the
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout'
--     structures or the @stencilLayout@ member of the
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentReferenceStencilLayout'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT' or
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--
-- -   If any of the @initialLayout@ members of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures specified when
--     creating the render pass specified in the @renderPass@ member of
--     @pRenderPassBegin@ is not
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED', then each
--     such @initialLayout@ /must/ be equal to the current layout of the
--     corresponding attachment image subresource of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@
--
-- -   The @srcStageMask@ and @dstStageMask@ members of any element of the
--     @pDependencies@ member of 'Vulkan.Core10.Pass.RenderPassCreateInfo'
--     used to create @renderPass@ /must/ be supported by the capabilities
--     of the queue family identified by the @queueFamilyIndex@ member of
--     the 'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' used to create
--     the command pool which @commandBuffer@ was allocated from
--
-- -   For any attachment in @framebuffer@ that is used by @renderPass@ and
--     is bound to memory locations that are also bound to another
--     attachment used by @renderPass@, and if at least one of those uses
--     causes either attachment to be written to, both attachments /must/
--     have had the
--     'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT'
--     set
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pInputAttachments@ of any element
--     of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     containing at least
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--     or
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pColorAttachments@ of any element
--     of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     containing
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pResolveAttachments@ of any
--     element of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     containing
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pDepthStencilAttachment@ of any
--     element of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     containing
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pRenderPassBegin@ /must/ be a valid pointer to a valid
--     'RenderPassBeginInfo' structure
--
-- -   @contents@ /must/ be a valid
--     'Vulkan.Core10.Enums.SubpassContents.SubpassContents' value
--
-- -   @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 operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- == 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                                                                                                                | Graphics                                                                                                              | Graphics                                                                                                                            |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'RenderPassBeginInfo',
-- 'Vulkan.Core10.Enums.SubpassContents.SubpassContents'
cmdBeginRenderPass :: forall a io
                    . (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io)
                   => -- | @commandBuffer@ is the command buffer in which to record the command.
                      CommandBuffer
                   -> -- | @pRenderPassBegin@ is a pointer to a 'RenderPassBeginInfo' structure
                      -- specifying the render pass to begin an instance of, and the framebuffer
                      -- the instance uses.
                      (RenderPassBeginInfo a)
                   -> -- | @contents@ is a 'Vulkan.Core10.Enums.SubpassContents.SubpassContents'
                      -- value specifying how the commands in the first subpass will be provided.
                      SubpassContents
                   -> io ()
cmdBeginRenderPass :: CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io ()
cmdBeginRenderPass commandBuffer :: CommandBuffer
commandBuffer renderPassBegin :: RenderPassBeginInfo a
renderPassBegin contents :: SubpassContents
contents = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdBeginRenderPassPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> SubpassContents
   -> IO ())
vkCmdBeginRenderPassPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
      -> SubpassContents
      -> IO ())
pVkCmdBeginRenderPass (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> SubpassContents
   -> IO ())
vkCmdBeginRenderPassPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> SubpassContents
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
      -> SubpassContents
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> SubpassContents
   -> 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 vkCmdBeginRenderPass is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBeginRenderPass' :: Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
-> SubpassContents
-> IO ()
vkCmdBeginRenderPass' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> SubpassContents
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
-> SubpassContents
-> IO ()
mkVkCmdBeginRenderPass FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> SubpassContents
   -> IO ())
vkCmdBeginRenderPassPtr
  Ptr (RenderPassBeginInfo a)
pRenderPassBegin <- ((Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ())
-> ContT () IO (Ptr (RenderPassBeginInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (RenderPassBeginInfo a)))
-> ((Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ())
-> ContT () IO (Ptr (RenderPassBeginInfo a))
forall a b. (a -> b) -> a -> b
$ RenderPassBeginInfo a
-> (Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderPassBeginInfo a
renderPassBegin)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
-> SubpassContents
-> IO ()
vkCmdBeginRenderPass' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Ptr (RenderPassBeginInfo a)
-> "pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (RenderPassBeginInfo a)
pRenderPassBegin) (SubpassContents
contents)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()

-- | This function will call the supplied action between calls to
-- 'cmdBeginRenderPass' and 'cmdEndRenderPass'
--
-- Note that 'cmdEndRenderPass' is *not* called if an exception is thrown
-- by the inner action.
cmdUseRenderPass :: forall a io r . (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io r -> io r
cmdUseRenderPass :: CommandBuffer
-> RenderPassBeginInfo a -> SubpassContents -> io r -> io r
cmdUseRenderPass commandBuffer :: CommandBuffer
commandBuffer pRenderPassBegin :: RenderPassBeginInfo a
pRenderPassBegin contents :: SubpassContents
contents a :: io r
a =
  (CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io ()
forall (a :: [*]) (io :: * -> *).
(Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) =>
CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io ()
cmdBeginRenderPass CommandBuffer
commandBuffer RenderPassBeginInfo a
pRenderPassBegin SubpassContents
contents) io () -> io r -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a io r -> io () -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (CommandBuffer -> io ()
forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
cmdEndRenderPass CommandBuffer
commandBuffer)


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

-- | vkCmdNextSubpass - Transition to the next subpass of a render pass
--
-- = Description
--
-- The subpass index for a render pass begins at zero when
-- 'cmdBeginRenderPass' is recorded, and increments each time
-- 'cmdNextSubpass' is recorded.
--
-- Moving to the next subpass automatically performs any multisample
-- resolve operations in the subpass being ended. End-of-subpass
-- multisample resolves are treated as color attachment writes for the
-- purposes of synchronization. This applies to resolve operations for both
-- color and depth\/stencil attachments. That is, they are considered to
-- execute in the
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT'
-- pipeline stage and their writes are synchronized with
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_COLOR_ATTACHMENT_WRITE_BIT'.
-- Synchronization between rendering within a subpass and any resolve
-- operations at the end of the subpass occurs automatically, without need
-- for explicit dependencies or pipeline barriers. However, if the resolve
-- attachment is also used in a different subpass, an explicit dependency
-- is needed.
--
-- After transitioning to the next subpass, the application /can/ record
-- the commands for that subpass.
--
-- == Valid Usage
--
-- -   The current subpass index /must/ be less than the number of
--     subpasses in the render pass minus one
--
-- -   This command /must/ not be recorded when transform feedback is
--     active
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @contents@ /must/ be a valid
--     'Vulkan.Core10.Enums.SubpassContents.SubpassContents' value
--
-- -   @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 operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- == 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.SubpassContents.SubpassContents'
cmdNextSubpass :: forall io
                . (MonadIO io)
               => -- | @commandBuffer@ is the command buffer in which to record the command.
                  CommandBuffer
               -> -- | @contents@ specifies how the commands in the next subpass will be
                  -- provided, in the same fashion as the corresponding parameter of
                  -- 'cmdBeginRenderPass'.
                  SubpassContents
               -> io ()
cmdNextSubpass :: CommandBuffer -> SubpassContents -> io ()
cmdNextSubpass commandBuffer :: CommandBuffer
commandBuffer contents :: SubpassContents
contents = 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 vkCmdNextSubpassPtr :: FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ())
vkCmdNextSubpassPtr = DeviceCmds
-> FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ())
pVkCmdNextSubpass (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ())
vkCmdNextSubpassPtr FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> SubpassContents -> 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 vkCmdNextSubpass is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdNextSubpass' :: Ptr CommandBuffer_T -> SubpassContents -> IO ()
vkCmdNextSubpass' = FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ())
-> Ptr CommandBuffer_T -> SubpassContents -> IO ()
mkVkCmdNextSubpass FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ())
vkCmdNextSubpassPtr
  Ptr CommandBuffer_T -> SubpassContents -> IO ()
vkCmdNextSubpass' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (SubpassContents
contents)
  () -> 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" mkVkCmdEndRenderPass
  :: FunPtr (Ptr CommandBuffer_T -> IO ()) -> Ptr CommandBuffer_T -> IO ()

-- | vkCmdEndRenderPass - End the current render pass
--
-- = Description
--
-- Ending a render pass instance performs any multisample resolve
-- operations on the final subpass.
--
-- == Valid Usage
--
-- -   The current subpass index /must/ be equal to the number of subpasses
--     in the render pass minus one
--
-- -   This command /must/ not be recorded when transform feedback is
--     active
--
-- == 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 operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- == 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                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdEndRenderPass :: forall io
                  . (MonadIO io)
                 => -- | @commandBuffer@ is the command buffer in which to end the current render
                    -- pass instance.
                    CommandBuffer
                 -> io ()
cmdEndRenderPass :: CommandBuffer -> io ()
cmdEndRenderPass commandBuffer :: CommandBuffer
commandBuffer = 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 vkCmdEndRenderPassPtr :: FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndRenderPassPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ())
pVkCmdEndRenderPass (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndRenderPassPtr FunPtr (Ptr CommandBuffer_T -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> 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 vkCmdEndRenderPass is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdEndRenderPass' :: Ptr CommandBuffer_T -> IO ()
vkCmdEndRenderPass' = FunPtr (Ptr CommandBuffer_T -> IO ())
-> Ptr CommandBuffer_T -> IO ()
mkVkCmdEndRenderPass FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndRenderPassPtr
  Ptr CommandBuffer_T -> IO ()
vkCmdEndRenderPass' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
  () -> 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" mkVkCmdExecuteCommands
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr (Ptr CommandBuffer_T) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr (Ptr CommandBuffer_T) -> IO ()

-- | vkCmdExecuteCommands - Execute a secondary command buffer from a primary
-- command buffer
--
-- = Description
--
-- If any element of @pCommandBuffers@ was not recorded with the
-- 'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT'
-- flag, and it was recorded into any other primary command buffer which is
-- currently in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle executable or recording state>,
-- that primary command buffer becomes
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle invalid>.
--
-- == Valid Usage
--
-- -   Each element of @pCommandBuffers@ /must/ have been allocated with a
--     @level@ of
--     'Vulkan.Core10.Enums.CommandBufferLevel.COMMAND_BUFFER_LEVEL_SECONDARY'
--
-- -   Each element of @pCommandBuffers@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending or executable state>
--
-- -   If any element of @pCommandBuffers@ was not recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT'
--     flag, it /must/ not be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>
--
-- -   If any element of @pCommandBuffers@ was not recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT'
--     flag, it /must/ not have already been recorded to @commandBuffer@
--
-- -   If any element of @pCommandBuffers@ was not recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT'
--     flag, it /must/ not appear more than once in @pCommandBuffers@
--
-- -   Each element of @pCommandBuffers@ /must/ have been allocated from a
--     'Vulkan.Core10.Handles.CommandPool' that was created for the same
--     queue family as the 'Vulkan.Core10.Handles.CommandPool' from which
--     @commandBuffer@ was allocated
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance, that render pass instance /must/ have been begun with the
--     @contents@ parameter of 'cmdBeginRenderPass' set to
--     'Vulkan.Core10.Enums.SubpassContents.SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS'
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance, each element of @pCommandBuffers@ /must/ have been
--     recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_RENDER_PASS_CONTINUE_BIT'
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance, each element of @pCommandBuffers@ /must/ have been
--     recorded with
--     'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo'::@subpass@
--     set to the index of the subpass which the given command buffer will
--     be executed in
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance, the render passes specified in the
--     @pBeginInfo->pInheritanceInfo->renderPass@ members of the
--     'Vulkan.Core10.CommandBuffer.beginCommandBuffer' commands used to
--     begin recording each element of @pCommandBuffers@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible>
--     with the current render pass
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance, and any element of @pCommandBuffers@ was recorded with
--     'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo'::@framebuffer@
--     not equal to 'Vulkan.Core10.APIConstants.NULL_HANDLE', that
--     'Vulkan.Core10.Handles.Framebuffer' /must/ match the
--     'Vulkan.Core10.Handles.Framebuffer' used in the current render pass
--     instance
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance that included
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'
--     in the @pNext@ chain of 'RenderPassBeginInfo', then each element of
--     @pCommandBuffers@ /must/ have been recorded with
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.CommandBufferInheritanceRenderPassTransformInfoQCOM'
--     in the @pNext@ chain of
--     'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance that included
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'
--     in the @pNext@ chain of 'RenderPassBeginInfo', then each element of
--     @pCommandBuffers@ /must/ have been recorded with
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.CommandBufferInheritanceRenderPassTransformInfoQCOM'::@transform@
--     identical to
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'::@transform@
--
-- -   If 'cmdExecuteCommands' is being called within a render pass
--     instance that included
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'
--     in the @pNext@ chain of 'RenderPassBeginInfo', then each element of
--     @pCommandBuffers@ /must/ have been recorded with
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.CommandBufferInheritanceRenderPassTransformInfoQCOM'::@renderArea@
--     identical to 'RenderPassBeginInfo'::@renderArea@
--
-- -   If 'cmdExecuteCommands' is not being called within a render pass
--     instance, each element of @pCommandBuffers@ /must/ not have been
--     recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_RENDER_PASS_CONTINUE_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-inheritedQueries inherited queries>
--     feature is not enabled, @commandBuffer@ /must/ not have any queries
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>
--
-- -   If @commandBuffer@ has a
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' query
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>,
--     then each element of @pCommandBuffers@ /must/ have been recorded
--     with
--     'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo'::@occlusionQueryEnable@
--     set to 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   If @commandBuffer@ has a
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' query
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>,
--     then each element of @pCommandBuffers@ /must/ have been recorded
--     with
--     'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo'::@queryFlags@
--     having all bits set that are set for the query
--
-- -   If @commandBuffer@ has a
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS' query
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>,
--     then each element of @pCommandBuffers@ /must/ have been recorded
--     with
--     'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo'::@pipelineStatistics@
--     having all bits set that are set in the
--     'Vulkan.Core10.Handles.QueryPool' the query uses
--
-- -   Each element of @pCommandBuffers@ /must/ not begin any query types
--     that are
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active>
--     in @commandBuffer@
--
-- -   If @commandBuffer@ is a protected command buffer, then each element
--     of @pCommandBuffers@ /must/ be a protected command buffer
--
-- -   If @commandBuffer@ is an unprotected command buffer, then each
--     element of @pCommandBuffers@ /must/ be an unprotected command buffer
--
-- -   This command /must/ not be recorded when transform feedback is
--     active
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pCommandBuffers@ /must/ be a valid pointer to an array of
--     @commandBufferCount@ valid 'Vulkan.Core10.Handles.CommandBuffer'
--     handles
--
-- -   @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 transfer, graphics, or compute
--     operations
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- -   @commandBufferCount@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and the elements of @pCommandBuffers@
--     /must/ have been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == 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                                                                                                                   | Transfer                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Graphics                                                                                                              |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdExecuteCommands :: forall io
                    . (MonadIO io)
                   => -- | @commandBuffer@ is a handle to a primary command buffer that the
                      -- secondary command buffers are executed in.
                      CommandBuffer
                   -> -- | @pCommandBuffers@ is a pointer to an array of @commandBufferCount@
                      -- secondary command buffer handles, which are recorded to execute in the
                      -- primary command buffer in the order they are listed in the array.
                      ("commandBuffers" ::: Vector CommandBuffer)
                   -> io ()
cmdExecuteCommands :: CommandBuffer
-> ("commandBuffers" ::: Vector CommandBuffer) -> io ()
cmdExecuteCommands commandBuffer :: CommandBuffer
commandBuffer commandBuffers :: "commandBuffers" ::: Vector CommandBuffer
commandBuffers = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdExecuteCommandsPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
   -> IO ())
vkCmdExecuteCommandsPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
      -> IO ())
pVkCmdExecuteCommands (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
   -> IO ())
vkCmdExecuteCommandsPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
   -> 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 vkCmdExecuteCommands is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdExecuteCommands' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ()
vkCmdExecuteCommands' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ()
mkVkCmdExecuteCommands FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
   -> IO ())
vkCmdExecuteCommandsPtr
  "pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers <- ((("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)) -> IO ())
 -> IO ())
-> ContT () IO ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)) -> IO ())
  -> IO ())
 -> ContT () IO ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)))
-> ((("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)) -> IO ())
    -> IO ())
-> ContT () IO ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CommandBuffer_T) ((("commandBuffers" ::: Vector CommandBuffer) -> Int
forall a. Vector a -> Int
Data.Vector.length ("commandBuffers" ::: Vector CommandBuffer
commandBuffers)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> CommandBuffer -> IO ())
-> ("commandBuffers" ::: Vector CommandBuffer) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: CommandBuffer
e -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> Ptr CommandBuffer_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> Int -> "pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CommandBuffer_T)) (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
e))) ("commandBuffers" ::: Vector CommandBuffer
commandBuffers)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ()
vkCmdExecuteCommands' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("commandBuffers" ::: Vector CommandBuffer) -> Int
forall a. Vector a -> Int
Data.Vector.length (("commandBuffers" ::: Vector CommandBuffer) -> Int)
-> ("commandBuffers" ::: Vector CommandBuffer) -> Int
forall a b. (a -> b) -> a -> b
$ ("commandBuffers" ::: Vector CommandBuffer
commandBuffers)) :: Word32)) ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkClearRect - Structure specifying a clear rectangle
--
-- = Description
--
-- The layers [@baseArrayLayer@, @baseArrayLayer@ + @layerCount@) counting
-- from the base layer of the attachment image view are cleared.
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Rect2D', 'cmdClearAttachments'
data ClearRect = ClearRect
  { -- | @rect@ is the two-dimensional region to be cleared.
    ClearRect -> Rect2D
rect :: Rect2D
  , -- | @baseArrayLayer@ is the first layer to be cleared.
    ClearRect -> "firstViewport" ::: Word32
baseArrayLayer :: Word32
  , -- | @layerCount@ is the number of layers to clear.
    ClearRect -> "firstViewport" ::: Word32
layerCount :: Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ClearRect)
#endif
deriving instance Show ClearRect

instance ToCStruct ClearRect where
  withCStruct :: ClearRect -> (("pRects" ::: Ptr ClearRect) -> IO b) -> IO b
withCStruct x :: ClearRect
x f :: ("pRects" ::: Ptr ClearRect) -> IO b
f = Int -> Int -> (("pRects" ::: Ptr ClearRect) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 4 ((("pRects" ::: Ptr ClearRect) -> IO b) -> IO b)
-> (("pRects" ::: Ptr ClearRect) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRects" ::: Ptr ClearRect
p -> ("pRects" ::: Ptr ClearRect) -> ClearRect -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRects" ::: Ptr ClearRect
p ClearRect
x (("pRects" ::: Ptr ClearRect) -> IO b
f "pRects" ::: Ptr ClearRect
p)
  pokeCStruct :: ("pRects" ::: Ptr ClearRect) -> ClearRect -> IO b -> IO b
pokeCStruct p :: "pRects" ::: Ptr ClearRect
p ClearRect{..} 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 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
$ ("pScissors" ::: Ptr Rect2D) -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect) -> Int -> "pScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Rect2D)) (Rect2D
rect) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> 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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("firstViewport" ::: Word32
baseArrayLayer)
    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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("firstViewport" ::: Word32
layerCount)
    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 = 24
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pRects" ::: Ptr ClearRect) -> IO b -> IO b
pokeZeroCStruct p :: "pRects" ::: Ptr ClearRect
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 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
$ ("pScissors" ::: Ptr Rect2D) -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect) -> Int -> "pScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Rect2D)) (Rect2D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> 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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    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 ClearRect where
  peekCStruct :: ("pRects" ::: Ptr ClearRect) -> IO ClearRect
peekCStruct p :: "pRects" ::: Ptr ClearRect
p = do
    Rect2D
rect <- ("pScissors" ::: Ptr Rect2D) -> IO Rect2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Rect2D (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect) -> Int -> "pScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Rect2D))
    "firstViewport" ::: Word32
baseArrayLayer <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "firstViewport" ::: Word32
layerCount <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pRects" ::: Ptr ClearRect
p ("pRects" ::: Ptr ClearRect)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    ClearRect -> IO ClearRect
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ClearRect -> IO ClearRect) -> ClearRect -> IO ClearRect
forall a b. (a -> b) -> a -> b
$ Rect2D
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ClearRect
ClearRect
             Rect2D
rect "firstViewport" ::: Word32
baseArrayLayer "firstViewport" ::: Word32
layerCount

instance Zero ClearRect where
  zero :: ClearRect
zero = Rect2D
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ClearRect
ClearRect
           Rect2D
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero


-- | VkImageSubresourceLayers - Structure specifying an image subresource
-- layers
--
-- == Valid Usage
--
-- -   If @aspectMask@ contains
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', it
--     /must/ not contain either of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--
-- -   @aspectMask@ /must/ not contain
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT'
--
-- -   @aspectMask@ /must/ not include
--     @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index @i@
--
-- -   @layerCount@ /must/ be greater than 0
--
-- == Valid Usage (Implicit)
--
-- -   @aspectMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values
--
-- -   @aspectMask@ /must/ not be @0@
--
-- = See Also
--
-- 'BufferImageCopy',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.BufferImageCopy2KHR',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags', 'ImageBlit',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.ImageBlit2KHR', 'ImageCopy',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.ImageCopy2KHR', 'ImageResolve',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.ImageResolve2KHR'
data ImageSubresourceLayers = ImageSubresourceLayers
  { -- | @aspectMask@ is a combination of
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits', selecting
    -- the color, depth and\/or stencil aspects to be copied.
    ImageSubresourceLayers -> ImageAspectFlags
aspectMask :: ImageAspectFlags
  , -- | @mipLevel@ is the mipmap level to copy from.
    ImageSubresourceLayers -> "firstViewport" ::: Word32
mipLevel :: Word32
  , -- | @baseArrayLayer@ and @layerCount@ are the starting layer and number of
    -- layers to copy.
    ImageSubresourceLayers -> "firstViewport" ::: Word32
baseArrayLayer :: Word32
  , -- No documentation found for Nested "VkImageSubresourceLayers" "layerCount"
    ImageSubresourceLayers -> "firstViewport" ::: Word32
layerCount :: Word32
  }
  deriving (Typeable, ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
(ImageSubresourceLayers -> ImageSubresourceLayers -> Bool)
-> (ImageSubresourceLayers -> ImageSubresourceLayers -> Bool)
-> Eq ImageSubresourceLayers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
$c/= :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
== :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
$c== :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageSubresourceLayers)
#endif
deriving instance Show ImageSubresourceLayers

instance ToCStruct ImageSubresourceLayers where
  withCStruct :: ImageSubresourceLayers
-> (Ptr ImageSubresourceLayers -> IO b) -> IO b
withCStruct x :: ImageSubresourceLayers
x f :: Ptr ImageSubresourceLayers -> IO b
f = Int -> Int -> (Ptr ImageSubresourceLayers -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr ImageSubresourceLayers -> IO b) -> IO b)
-> (Ptr ImageSubresourceLayers -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImageSubresourceLayers
p -> Ptr ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageSubresourceLayers
p ImageSubresourceLayers
x (Ptr ImageSubresourceLayers -> IO b
f Ptr ImageSubresourceLayers
p)
  pokeCStruct :: Ptr ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
pokeCStruct p :: Ptr ImageSubresourceLayers
p ImageSubresourceLayers{..} f :: IO b
f = do
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("firstViewport" ::: Word32
mipLevel)
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("firstViewport" ::: Word32
baseArrayLayer)
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("firstViewport" ::: Word32
layerCount)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr ImageSubresourceLayers -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImageSubresourceLayers
p f :: IO b
f = do
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
forall a. Zero a => a
zero)
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImageSubresourceLayers where
  peekCStruct :: Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
peekCStruct p :: Ptr ImageSubresourceLayers
p = do
    ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags))
    "firstViewport" ::: Word32
mipLevel <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    "firstViewport" ::: Word32
baseArrayLayer <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    "firstViewport" ::: Word32
layerCount <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    ImageSubresourceLayers -> IO ImageSubresourceLayers
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageSubresourceLayers -> IO ImageSubresourceLayers)
-> ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a b. (a -> b) -> a -> b
$ ImageAspectFlags
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ImageSubresourceLayers
ImageSubresourceLayers
             ImageAspectFlags
aspectMask "firstViewport" ::: Word32
mipLevel "firstViewport" ::: Word32
baseArrayLayer "firstViewport" ::: Word32
layerCount

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

instance Zero ImageSubresourceLayers where
  zero :: ImageSubresourceLayers
zero = ImageAspectFlags
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ImageSubresourceLayers
ImageSubresourceLayers
           ImageAspectFlags
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero


-- | VkBufferCopy - Structure specifying a buffer copy operation
--
-- == Valid Usage
--
-- -   The @size@ /must/ be greater than @0@
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize', 'cmdCopyBuffer'
data BufferCopy = BufferCopy
  { -- | @srcOffset@ is the starting offset in bytes from the start of
    -- @srcBuffer@.
    BufferCopy -> "offset" ::: DeviceSize
srcOffset :: DeviceSize
  , -- | @dstOffset@ is the starting offset in bytes from the start of
    -- @dstBuffer@.
    BufferCopy -> "offset" ::: DeviceSize
dstOffset :: DeviceSize
  , -- | @size@ is the number of bytes to copy.
    BufferCopy -> "offset" ::: DeviceSize
size :: DeviceSize
  }
  deriving (Typeable, BufferCopy -> BufferCopy -> Bool
(BufferCopy -> BufferCopy -> Bool)
-> (BufferCopy -> BufferCopy -> Bool) -> Eq BufferCopy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferCopy -> BufferCopy -> Bool
$c/= :: BufferCopy -> BufferCopy -> Bool
== :: BufferCopy -> BufferCopy -> Bool
$c== :: BufferCopy -> BufferCopy -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferCopy)
#endif
deriving instance Show BufferCopy

instance ToCStruct BufferCopy where
  withCStruct :: BufferCopy -> (("pRegions" ::: Ptr BufferCopy) -> IO b) -> IO b
withCStruct x :: BufferCopy
x f :: ("pRegions" ::: Ptr BufferCopy) -> IO b
f = Int -> Int -> (("pRegions" ::: Ptr BufferCopy) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pRegions" ::: Ptr BufferCopy) -> IO b) -> IO b)
-> (("pRegions" ::: Ptr BufferCopy) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRegions" ::: Ptr BufferCopy
p -> ("pRegions" ::: Ptr BufferCopy) -> BufferCopy -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRegions" ::: Ptr BufferCopy
p BufferCopy
x (("pRegions" ::: Ptr BufferCopy) -> IO b
f "pRegions" ::: Ptr BufferCopy
p)
  pokeCStruct :: ("pRegions" ::: Ptr BufferCopy) -> BufferCopy -> IO b -> IO b
pokeCStruct p :: "pRegions" ::: Ptr BufferCopy
p BufferCopy{..} f :: IO b
f = do
    ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
srcOffset)
    ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
dstOffset)
    ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
size)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pRegions" ::: Ptr BufferCopy) -> IO b -> IO b
pokeZeroCStruct p :: "pRegions" ::: Ptr BufferCopy
p f :: IO b
f = do
    ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
    ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
    ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct BufferCopy where
  peekCStruct :: ("pRegions" ::: Ptr BufferCopy) -> IO BufferCopy
peekCStruct p :: "pRegions" ::: Ptr BufferCopy
p = do
    "offset" ::: DeviceSize
srcOffset <- ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
    "offset" ::: DeviceSize
dstOffset <- ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
    "offset" ::: DeviceSize
size <- ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRegions" ::: Ptr BufferCopy
p ("pRegions" ::: Ptr BufferCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
    BufferCopy -> IO BufferCopy
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferCopy -> IO BufferCopy) -> BufferCopy -> IO BufferCopy
forall a b. (a -> b) -> a -> b
$ ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> BufferCopy
BufferCopy
             "offset" ::: DeviceSize
srcOffset "offset" ::: DeviceSize
dstOffset "offset" ::: DeviceSize
size

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

instance Zero BufferCopy where
  zero :: BufferCopy
zero = ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> BufferCopy
BufferCopy
           "offset" ::: DeviceSize
forall a. Zero a => a
zero
           "offset" ::: DeviceSize
forall a. Zero a => a
zero
           "offset" ::: DeviceSize
forall a. Zero a => a
zero


-- | VkImageCopy - Structure specifying an image copy operation
--
-- = Description
--
-- For 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' images, copies are
-- performed slice by slice starting with the @z@ member of the @srcOffset@
-- or @dstOffset@, and copying @depth@ slices. For images with multiple
-- layers, copies are performed layer by layer starting with the
-- @baseArrayLayer@ member of the @srcSubresource@ or @dstSubresource@ and
-- copying @layerCount@ layers. Image data /can/ be copied between images
-- with different image types. If one image is
-- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' and the other image is
-- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' with multiple layers, then
-- each slice is copied to or from a different layer.
--
-- Copies involving a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>
-- specify the region to be copied in terms of the /plane/ to be copied,
-- not the coordinates of the multi-planar image. This means that copies
-- accessing the R\/B planes of “@_422@” format images /must/ fit the
-- copied region within half the @width@ of the parent image, and that
-- copies accessing the R\/B planes of “@_420@” format images /must/ fit
-- the copied region within half the @width@ and @height@ of the parent
-- image.
--
-- == Valid Usage
--
-- -   The number of slices of the @extent@ (for 3D) or layers of the
--     @srcSubresource@ (for non-3D) /must/ match the number of slices of
--     the @extent@ (for 3D) or layers of the @dstSubresource@ (for non-3D)
--
-- == Valid Usage (Implicit)
--
-- -   @srcSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- -   @dstSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Extent3D', 'ImageSubresourceLayers',
-- 'Vulkan.Core10.FundamentalTypes.Offset3D', 'cmdCopyImage'
data ImageCopy = ImageCopy
  { -- | @srcSubresource@ and @dstSubresource@ are 'ImageSubresourceLayers'
    -- structures specifying the image subresources of the images used for the
    -- source and destination image data, respectively.
    ImageCopy -> ImageSubresourceLayers
srcSubresource :: ImageSubresourceLayers
  , -- | @srcOffset@ and @dstOffset@ select the initial @x@, @y@, and @z@ offsets
    -- in texels of the sub-regions of the source and destination image data.
    ImageCopy -> Offset3D
srcOffset :: Offset3D
  , -- No documentation found for Nested "VkImageCopy" "dstSubresource"
    ImageCopy -> ImageSubresourceLayers
dstSubresource :: ImageSubresourceLayers
  , -- No documentation found for Nested "VkImageCopy" "dstOffset"
    ImageCopy -> Offset3D
dstOffset :: Offset3D
  , -- | @extent@ is the size in texels of the image to copy in @width@, @height@
    -- and @depth@.
    ImageCopy -> Extent3D
extent :: Extent3D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageCopy)
#endif
deriving instance Show ImageCopy

instance ToCStruct ImageCopy where
  withCStruct :: ImageCopy -> (("pRegions" ::: Ptr ImageCopy) -> IO b) -> IO b
withCStruct x :: ImageCopy
x f :: ("pRegions" ::: Ptr ImageCopy) -> IO b
f = Int -> Int -> (("pRegions" ::: Ptr ImageCopy) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 68 4 ((("pRegions" ::: Ptr ImageCopy) -> IO b) -> IO b)
-> (("pRegions" ::: Ptr ImageCopy) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRegions" ::: Ptr ImageCopy
p -> ("pRegions" ::: Ptr ImageCopy) -> ImageCopy -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRegions" ::: Ptr ImageCopy
p ImageCopy
x (("pRegions" ::: Ptr ImageCopy) -> IO b
f "pRegions" ::: Ptr ImageCopy
p)
  pokeCStruct :: ("pRegions" ::: Ptr ImageCopy) -> ImageCopy -> IO b -> IO b
pokeCStruct p :: "pRegions" ::: Ptr ImageCopy
p ImageCopy{..} 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 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
srcSubresource) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Offset3D)) (Offset3D
srcOffset) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
dstSubresource) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Offset3D)) (Offset3D
dstOffset) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Extent3D)) (Extent3D
extent) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 68
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pRegions" ::: Ptr ImageCopy) -> IO b -> IO b
pokeZeroCStruct p :: "pRegions" ::: Ptr ImageCopy
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 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Offset3D)) (Offset3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Offset3D)) (Offset3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Extent3D)) (Extent3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct ImageCopy where
  peekCStruct :: ("pRegions" ::: Ptr ImageCopy) -> IO ImageCopy
peekCStruct p :: "pRegions" ::: Ptr ImageCopy
p = do
    ImageSubresourceLayers
srcSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers))
    Offset3D
srcOffset <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Offset3D))
    ImageSubresourceLayers
dstSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageSubresourceLayers))
    Offset3D
dstOffset <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Offset3D))
    Extent3D
extent <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pRegions" ::: Ptr ImageCopy
p ("pRegions" ::: Ptr ImageCopy) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Extent3D))
    ImageCopy -> IO ImageCopy
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageCopy -> IO ImageCopy) -> ImageCopy -> IO ImageCopy
forall a b. (a -> b) -> a -> b
$ ImageSubresourceLayers
-> Offset3D
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> ImageCopy
ImageCopy
             ImageSubresourceLayers
srcSubresource Offset3D
srcOffset ImageSubresourceLayers
dstSubresource Offset3D
dstOffset Extent3D
extent

instance Zero ImageCopy where
  zero :: ImageCopy
zero = ImageSubresourceLayers
-> Offset3D
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> ImageCopy
ImageCopy
           ImageSubresourceLayers
forall a. Zero a => a
zero
           Offset3D
forall a. Zero a => a
zero
           ImageSubresourceLayers
forall a. Zero a => a
zero
           Offset3D
forall a. Zero a => a
zero
           Extent3D
forall a. Zero a => a
zero


-- | VkImageBlit - Structure specifying an image blit operation
--
-- = Description
--
-- For each element of the @pRegions@ array, a blit operation is performed
-- the specified source and destination regions.
--
-- == Valid Usage
--
-- -   The @aspectMask@ member of @srcSubresource@ and @dstSubresource@
--     /must/ match
--
-- -   The @layerCount@ member of @srcSubresource@ and @dstSubresource@
--     /must/ match
--
-- == Valid Usage (Implicit)
--
-- -   @srcSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- -   @dstSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- = See Also
--
-- 'ImageSubresourceLayers', 'Vulkan.Core10.FundamentalTypes.Offset3D',
-- 'cmdBlitImage'
data ImageBlit = ImageBlit
  { -- | @srcSubresource@ is the subresource to blit from.
    ImageBlit -> ImageSubresourceLayers
srcSubresource :: ImageSubresourceLayers
  , -- | @srcOffsets@ is a pointer to an array of two
    -- 'Vulkan.Core10.FundamentalTypes.Offset3D' structures specifying the
    -- bounds of the source region within @srcSubresource@.
    ImageBlit -> (Offset3D, Offset3D)
srcOffsets :: (Offset3D, Offset3D)
  , -- | @dstSubresource@ is the subresource to blit into.
    ImageBlit -> ImageSubresourceLayers
dstSubresource :: ImageSubresourceLayers
  , -- | @dstOffsets@ is a pointer to an array of two
    -- 'Vulkan.Core10.FundamentalTypes.Offset3D' structures specifying the
    -- bounds of the destination region within @dstSubresource@.
    ImageBlit -> (Offset3D, Offset3D)
dstOffsets :: (Offset3D, Offset3D)
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageBlit)
#endif
deriving instance Show ImageBlit

instance ToCStruct ImageBlit where
  withCStruct :: ImageBlit -> (("pRegions" ::: Ptr ImageBlit) -> IO b) -> IO b
withCStruct x :: ImageBlit
x f :: ("pRegions" ::: Ptr ImageBlit) -> IO b
f = Int -> Int -> (("pRegions" ::: Ptr ImageBlit) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 80 4 ((("pRegions" ::: Ptr ImageBlit) -> IO b) -> IO b)
-> (("pRegions" ::: Ptr ImageBlit) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRegions" ::: Ptr ImageBlit
p -> ("pRegions" ::: Ptr ImageBlit) -> ImageBlit -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRegions" ::: Ptr ImageBlit
p ImageBlit
x (("pRegions" ::: Ptr ImageBlit) -> IO b
f "pRegions" ::: Ptr ImageBlit
p)
  pokeCStruct :: ("pRegions" ::: Ptr ImageBlit) -> ImageBlit -> IO b -> IO b
pokeCStruct p :: "pRegions" ::: Ptr ImageBlit
p ImageBlit{..} 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 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
srcSubresource) (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
$ ())
    let pSrcOffsets' :: Ptr Offset3D
pSrcOffsets' = Ptr (FixedArray 2 Offset3D) -> Ptr Offset3D
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit)
-> Int -> Ptr (FixedArray 2 Offset3D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray 2 Offset3D)))
    case ((Offset3D, Offset3D)
srcOffsets) of
      (e0 :: Offset3D
e0, e1 :: Offset3D
e1) -> do
        ((() -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pSrcOffsets' :: Ptr Offset3D) (Offset3D
e0) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
        ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pSrcOffsets' Ptr Offset3D -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D) (Offset3D
e1) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
dstSubresource) (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
$ ())
    let pDstOffsets' :: Ptr Offset3D
pDstOffsets' = Ptr (FixedArray 2 Offset3D) -> Ptr Offset3D
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit)
-> Int -> Ptr (FixedArray 2 Offset3D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (FixedArray 2 Offset3D)))
    case ((Offset3D, Offset3D)
dstOffsets) of
      (e0 :: Offset3D
e0, e1 :: Offset3D
e1) -> do
        ((() -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pDstOffsets' :: Ptr Offset3D) (Offset3D
e0) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
        ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pDstOffsets' Ptr Offset3D -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D) (Offset3D
e1) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 80
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pRegions" ::: Ptr ImageBlit) -> IO b -> IO b
pokeZeroCStruct p :: "pRegions" ::: Ptr ImageBlit
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 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    let pSrcOffsets' :: Ptr Offset3D
pSrcOffsets' = Ptr (FixedArray 2 Offset3D) -> Ptr Offset3D
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit)
-> Int -> Ptr (FixedArray 2 Offset3D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray 2 Offset3D)))
    case ((Offset3D
forall a. Zero a => a
zero, Offset3D
forall a. Zero a => a
zero)) of
      (e0 :: Offset3D
e0, e1 :: Offset3D
e1) -> do
        ((() -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pSrcOffsets' :: Ptr Offset3D) (Offset3D
e0) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
        ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pSrcOffsets' Ptr Offset3D -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D) (Offset3D
e1) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    let pDstOffsets' :: Ptr Offset3D
pDstOffsets' = Ptr (FixedArray 2 Offset3D) -> Ptr Offset3D
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit)
-> Int -> Ptr (FixedArray 2 Offset3D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (FixedArray 2 Offset3D)))
    case ((Offset3D
forall a. Zero a => a
zero, Offset3D
forall a. Zero a => a
zero)) of
      (e0 :: Offset3D
e0, e1 :: Offset3D
e1) -> do
        ((() -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pDstOffsets' :: Ptr Offset3D) (Offset3D
e0) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
        ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Offset3D
pDstOffsets' Ptr Offset3D -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Offset3D) (Offset3D
e1) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct ImageBlit where
  peekCStruct :: ("pRegions" ::: Ptr ImageBlit) -> IO ImageBlit
peekCStruct p :: "pRegions" ::: Ptr ImageBlit
p = do
    ImageSubresourceLayers
srcSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers))
    let psrcOffsets :: Ptr Offset3D
psrcOffsets = Ptr (FixedArray 2 Offset3D) -> Ptr Offset3D
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Offset3D (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit)
-> Int -> Ptr (FixedArray 2 Offset3D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray 2 Offset3D)))
    Offset3D
srcOffsets0 <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D ((Ptr Offset3D
psrcOffsets Ptr Offset3D -> Int -> Ptr Offset3D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Offset3D))
    Offset3D
srcOffsets1 <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D ((Ptr Offset3D
psrcOffsets Ptr Offset3D -> Int -> Ptr Offset3D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 12 :: Ptr Offset3D))
    ImageSubresourceLayers
dstSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit) -> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ImageSubresourceLayers))
    let pdstOffsets :: Ptr Offset3D
pdstOffsets = Ptr (FixedArray 2 Offset3D) -> Ptr Offset3D
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Offset3D (("pRegions" ::: Ptr ImageBlit
p ("pRegions" ::: Ptr ImageBlit)
-> Int -> Ptr (FixedArray 2 Offset3D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (FixedArray 2 Offset3D)))
    Offset3D
dstOffsets0 <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D ((Ptr Offset3D
pdstOffsets Ptr Offset3D -> Int -> Ptr Offset3D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Offset3D))
    Offset3D
dstOffsets1 <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D ((Ptr Offset3D
pdstOffsets Ptr Offset3D -> Int -> Ptr Offset3D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 12 :: Ptr Offset3D))
    ImageBlit -> IO ImageBlit
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageBlit -> IO ImageBlit) -> ImageBlit -> IO ImageBlit
forall a b. (a -> b) -> a -> b
$ ImageSubresourceLayers
-> (Offset3D, Offset3D)
-> ImageSubresourceLayers
-> (Offset3D, Offset3D)
-> ImageBlit
ImageBlit
             ImageSubresourceLayers
srcSubresource ((Offset3D
srcOffsets0, Offset3D
srcOffsets1)) ImageSubresourceLayers
dstSubresource ((Offset3D
dstOffsets0, Offset3D
dstOffsets1))

instance Zero ImageBlit where
  zero :: ImageBlit
zero = ImageSubresourceLayers
-> (Offset3D, Offset3D)
-> ImageSubresourceLayers
-> (Offset3D, Offset3D)
-> ImageBlit
ImageBlit
           ImageSubresourceLayers
forall a. Zero a => a
zero
           (Offset3D
forall a. Zero a => a
zero, Offset3D
forall a. Zero a => a
zero)
           ImageSubresourceLayers
forall a. Zero a => a
zero
           (Offset3D
forall a. Zero a => a
zero, Offset3D
forall a. Zero a => a
zero)


-- | VkBufferImageCopy - Structure specifying a buffer image copy operation
--
-- = Description
--
-- When copying to or from a depth or stencil aspect, the data in buffer
-- memory uses a layout that is a (mostly) tightly packed representation of
-- the depth or stencil data. Specifically:
--
-- -   data copied to or from the stencil aspect of any depth\/stencil
--     format is tightly packed with one
--     'Vulkan.Core10.Enums.Format.FORMAT_S8_UINT' value per texel.
--
-- -   data copied to or from the depth aspect of a
--     'Vulkan.Core10.Enums.Format.FORMAT_D16_UNORM' or
--     'Vulkan.Core10.Enums.Format.FORMAT_D16_UNORM_S8_UINT' format is
--     tightly packed with one
--     'Vulkan.Core10.Enums.Format.FORMAT_D16_UNORM' value per texel.
--
-- -   data copied to or from the depth aspect of a
--     'Vulkan.Core10.Enums.Format.FORMAT_D32_SFLOAT' or
--     'Vulkan.Core10.Enums.Format.FORMAT_D32_SFLOAT_S8_UINT' format is
--     tightly packed with one
--     'Vulkan.Core10.Enums.Format.FORMAT_D32_SFLOAT' value per texel.
--
-- -   data copied to or from the depth aspect of a
--     'Vulkan.Core10.Enums.Format.FORMAT_X8_D24_UNORM_PACK32' or
--     'Vulkan.Core10.Enums.Format.FORMAT_D24_UNORM_S8_UINT' format is
--     packed with one 32-bit word per texel with the D24 value in the LSBs
--     of the word, and undefined values in the eight MSBs.
--
-- Note
--
-- To copy both the depth and stencil aspects of a depth\/stencil format,
-- two entries in @pRegions@ /can/ be used, where one specifies the depth
-- aspect in @imageSubresource@, and the other specifies the stencil
-- aspect.
--
-- Because depth or stencil aspect buffer to image copies /may/ require
-- format conversions on some implementations, they are not supported on
-- queues that do not support graphics.
--
-- When copying to a depth aspect, and the
-- @VK_EXT_depth_range_unrestricted@ extension is not enabled, the data in
-- buffer memory /must/ be in the range [0,1], or the resulting values are
-- undefined.
--
-- Copies are done layer by layer starting with image layer
-- @baseArrayLayer@ member of @imageSubresource@. @layerCount@ layers are
-- copied from the source image or to the destination image.
--
-- For purpose of valid usage statements here and in related copy commands,
-- a /blocked image/ is defined as:
--
-- -   a image with a /single-plane/, “@_422@” format, which is treated as
--     a format with a 2 × 1 compressed texel block, or
--
-- -   a compressed image.
--
-- == Valid Usage
--
-- -   @bufferRowLength@ /must/ be @0@, or greater than or equal to the
--     @width@ member of @imageExtent@
--
-- -   @bufferImageHeight@ /must/ be @0@, or greater than or equal to the
--     @height@ member of @imageExtent@
--
-- -   The @aspectMask@ member of @imageSubresource@ /must/ only have a
--     single bit set
--
-- == Valid Usage (Implicit)
--
-- -   @imageSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.FundamentalTypes.Extent3D', 'ImageSubresourceLayers',
-- 'Vulkan.Core10.FundamentalTypes.Offset3D', 'cmdCopyBufferToImage',
-- 'cmdCopyImageToBuffer'
data BufferImageCopy = BufferImageCopy
  { -- | @bufferOffset@ is the offset in bytes from the start of the buffer
    -- object where the image data is copied from or to.
    BufferImageCopy -> "offset" ::: DeviceSize
bufferOffset :: DeviceSize
  , -- | @bufferRowLength@ and @bufferImageHeight@ specify in texels a subregion
    -- of a larger two- or three-dimensional image in buffer memory, and
    -- control the addressing calculations. If either of these values is zero,
    -- that aspect of the buffer memory is considered to be tightly packed
    -- according to the @imageExtent@.
    BufferImageCopy -> "firstViewport" ::: Word32
bufferRowLength :: Word32
  , -- No documentation found for Nested "VkBufferImageCopy" "bufferImageHeight"
    BufferImageCopy -> "firstViewport" ::: Word32
bufferImageHeight :: Word32
  , -- | @imageSubresource@ is a 'ImageSubresourceLayers' used to specify the
    -- specific image subresources of the image used for the source or
    -- destination image data.
    BufferImageCopy -> ImageSubresourceLayers
imageSubresource :: ImageSubresourceLayers
  , -- | @imageOffset@ selects the initial @x@, @y@, @z@ offsets in texels of the
    -- sub-region of the source or destination image data.
    BufferImageCopy -> Offset3D
imageOffset :: Offset3D
  , -- | @imageExtent@ is the size in texels of the image to copy in @width@,
    -- @height@ and @depth@.
    BufferImageCopy -> Extent3D
imageExtent :: Extent3D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferImageCopy)
#endif
deriving instance Show BufferImageCopy

instance ToCStruct BufferImageCopy where
  withCStruct :: BufferImageCopy
-> (("pRegions" ::: Ptr BufferImageCopy) -> IO b) -> IO b
withCStruct x :: BufferImageCopy
x f :: ("pRegions" ::: Ptr BufferImageCopy) -> IO b
f = Int
-> Int -> (("pRegions" ::: Ptr BufferImageCopy) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((("pRegions" ::: Ptr BufferImageCopy) -> IO b) -> IO b)
-> (("pRegions" ::: Ptr BufferImageCopy) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRegions" ::: Ptr BufferImageCopy
p -> ("pRegions" ::: Ptr BufferImageCopy)
-> BufferImageCopy -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRegions" ::: Ptr BufferImageCopy
p BufferImageCopy
x (("pRegions" ::: Ptr BufferImageCopy) -> IO b
f "pRegions" ::: Ptr BufferImageCopy
p)
  pokeCStruct :: ("pRegions" ::: Ptr BufferImageCopy)
-> BufferImageCopy -> IO b -> IO b
pokeCStruct p :: "pRegions" ::: Ptr BufferImageCopy
p BufferImageCopy{..} 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
$ ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
bufferOffset)
    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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("firstViewport" ::: Word32
bufferRowLength)
    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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("firstViewport" ::: Word32
bufferImageHeight)
    ((() -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
imageSubresource) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Offset3D)) (Offset3D
imageOffset) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Extent3D)) (Extent3D
imageExtent) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pRegions" ::: Ptr BufferImageCopy) -> IO b -> IO b
pokeZeroCStruct p :: "pRegions" ::: Ptr BufferImageCopy
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
$ ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Offset3D)) (Offset3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Extent3D)) (Extent3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct BufferImageCopy where
  peekCStruct :: ("pRegions" ::: Ptr BufferImageCopy) -> IO BufferImageCopy
peekCStruct p :: "pRegions" ::: Ptr BufferImageCopy
p = do
    "offset" ::: DeviceSize
bufferOffset <- ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
    "firstViewport" ::: Word32
bufferRowLength <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    "firstViewport" ::: Word32
bufferImageHeight <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    ImageSubresourceLayers
imageSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageSubresourceLayers))
    Offset3D
imageOffset <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Offset3D))
    Extent3D
imageExtent <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pRegions" ::: Ptr BufferImageCopy
p ("pRegions" ::: Ptr BufferImageCopy) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Extent3D))
    BufferImageCopy -> IO BufferImageCopy
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferImageCopy -> IO BufferImageCopy)
-> BufferImageCopy -> IO BufferImageCopy
forall a b. (a -> b) -> a -> b
$ ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> BufferImageCopy
BufferImageCopy
             "offset" ::: DeviceSize
bufferOffset "firstViewport" ::: Word32
bufferRowLength "firstViewport" ::: Word32
bufferImageHeight ImageSubresourceLayers
imageSubresource Offset3D
imageOffset Extent3D
imageExtent

instance Zero BufferImageCopy where
  zero :: BufferImageCopy
zero = ("offset" ::: DeviceSize)
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> BufferImageCopy
BufferImageCopy
           "offset" ::: DeviceSize
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           ImageSubresourceLayers
forall a. Zero a => a
zero
           Offset3D
forall a. Zero a => a
zero
           Extent3D
forall a. Zero a => a
zero


-- | VkImageResolve - Structure specifying an image resolve operation
--
-- == Valid Usage
--
-- -   The @aspectMask@ member of @srcSubresource@ and @dstSubresource@
--     /must/ only contain
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'
--
-- -   The @layerCount@ member of @srcSubresource@ and @dstSubresource@
--     /must/ match
--
-- == Valid Usage (Implicit)
--
-- -   @srcSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- -   @dstSubresource@ /must/ be a valid 'ImageSubresourceLayers'
--     structure
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Extent3D', 'ImageSubresourceLayers',
-- 'Vulkan.Core10.FundamentalTypes.Offset3D', 'cmdResolveImage'
data ImageResolve = ImageResolve
  { -- | @srcSubresource@ and @dstSubresource@ are 'ImageSubresourceLayers'
    -- structures specifying the image subresources of the images used for the
    -- source and destination image data, respectively. Resolve of
    -- depth\/stencil images is not supported.
    ImageResolve -> ImageSubresourceLayers
srcSubresource :: ImageSubresourceLayers
  , -- | @srcOffset@ and @dstOffset@ select the initial @x@, @y@, and @z@ offsets
    -- in texels of the sub-regions of the source and destination image data.
    ImageResolve -> Offset3D
srcOffset :: Offset3D
  , -- No documentation found for Nested "VkImageResolve" "dstSubresource"
    ImageResolve -> ImageSubresourceLayers
dstSubresource :: ImageSubresourceLayers
  , -- No documentation found for Nested "VkImageResolve" "dstOffset"
    ImageResolve -> Offset3D
dstOffset :: Offset3D
  , -- | @extent@ is the size in texels of the source image to resolve in
    -- @width@, @height@ and @depth@.
    ImageResolve -> Extent3D
extent :: Extent3D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageResolve)
#endif
deriving instance Show ImageResolve

instance ToCStruct ImageResolve where
  withCStruct :: ImageResolve -> (("pRegions" ::: Ptr ImageResolve) -> IO b) -> IO b
withCStruct x :: ImageResolve
x f :: ("pRegions" ::: Ptr ImageResolve) -> IO b
f = Int -> Int -> (("pRegions" ::: Ptr ImageResolve) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 68 4 ((("pRegions" ::: Ptr ImageResolve) -> IO b) -> IO b)
-> (("pRegions" ::: Ptr ImageResolve) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRegions" ::: Ptr ImageResolve
p -> ("pRegions" ::: Ptr ImageResolve) -> ImageResolve -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRegions" ::: Ptr ImageResolve
p ImageResolve
x (("pRegions" ::: Ptr ImageResolve) -> IO b
f "pRegions" ::: Ptr ImageResolve
p)
  pokeCStruct :: ("pRegions" ::: Ptr ImageResolve) -> ImageResolve -> IO b -> IO b
pokeCStruct p :: "pRegions" ::: Ptr ImageResolve
p ImageResolve{..} 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 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
srcSubresource) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Offset3D)) (Offset3D
srcOffset) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
dstSubresource) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Offset3D)) (Offset3D
dstOffset) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Extent3D)) (Extent3D
extent) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 68
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pRegions" ::: Ptr ImageResolve) -> IO b -> IO b
pokeZeroCStruct p :: "pRegions" ::: Ptr ImageResolve
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 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Offset3D)) (Offset3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Offset3D)) (Offset3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Extent3D)) (Extent3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct ImageResolve where
  peekCStruct :: ("pRegions" ::: Ptr ImageResolve) -> IO ImageResolve
peekCStruct p :: "pRegions" ::: Ptr ImageResolve
p = do
    ImageSubresourceLayers
srcSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageSubresourceLayers))
    Offset3D
srcOffset <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Offset3D))
    ImageSubresourceLayers
dstSubresource <- Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve)
-> Int -> Ptr ImageSubresourceLayers
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageSubresourceLayers))
    Offset3D
dstOffset <- Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset3D (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Offset3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Offset3D))
    Extent3D
extent <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pRegions" ::: Ptr ImageResolve
p ("pRegions" ::: Ptr ImageResolve) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Extent3D))
    ImageResolve -> IO ImageResolve
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageResolve -> IO ImageResolve)
-> ImageResolve -> IO ImageResolve
forall a b. (a -> b) -> a -> b
$ ImageSubresourceLayers
-> Offset3D
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> ImageResolve
ImageResolve
             ImageSubresourceLayers
srcSubresource Offset3D
srcOffset ImageSubresourceLayers
dstSubresource Offset3D
dstOffset Extent3D
extent

instance Zero ImageResolve where
  zero :: ImageResolve
zero = ImageSubresourceLayers
-> Offset3D
-> ImageSubresourceLayers
-> Offset3D
-> Extent3D
-> ImageResolve
ImageResolve
           ImageSubresourceLayers
forall a. Zero a => a
zero
           Offset3D
forall a. Zero a => a
zero
           ImageSubresourceLayers
forall a. Zero a => a
zero
           Offset3D
forall a. Zero a => a
zero
           Extent3D
forall a. Zero a => a
zero


-- | VkRenderPassBeginInfo - Structure specifying render pass begin info
--
-- = Description
--
-- @renderArea@ is the render area that is affected by the render pass
-- instance. The effects of attachment load, store and multisample resolve
-- operations are restricted to the pixels whose x and y coordinates fall
-- within the render area on all attachments. The render area extends to
-- all layers of @framebuffer@. The application /must/ ensure (using
-- scissor if necessary) that all rendering is contained within the render
-- area. The render area, after any transform specified by
-- 'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'::@transform@
-- is applied, /must/ be contained within the framebuffer dimensions.
--
-- If
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vertexpostproc-renderpass-transform render pass transform>
-- is enabled, then @renderArea@ /must/ equal the framebuffer
-- pre-transformed dimensions. After @renderArea@ has been transformed by
-- 'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'::@transform@,
-- the resulting render area /must/ be equal to the framebuffer dimensions.
--
-- When multiview is enabled, the resolve operation at the end of a subpass
-- applies to all views in the view mask.
--
-- Note
--
-- There /may/ be a performance cost for using a render area smaller than
-- the framebuffer, unless it matches the render area granularity for the
-- render pass.
--
-- == Valid Usage
--
-- -   @clearValueCount@ /must/ be greater than the largest attachment
--     index in @renderPass@ that specifies a @loadOp@ (or @stencilLoadOp@,
--     if the attachment has a depth\/stencil format) of
--     'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR'
--
-- -   @renderPass@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible>
--     with the @renderPass@ member of the
--     'Vulkan.Core10.Pass.FramebufferCreateInfo' structure specified when
--     creating @framebuffer@
--
-- -   If the @pNext@ chain does not contain
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo'
--     or its @deviceRenderAreaCount@ member is equal to 0,
--     @renderArea.offset.x@ /must/ be greater than or equal to 0
--
-- -   If the @pNext@ chain does not contain
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo'
--     or its @deviceRenderAreaCount@ member is equal to 0,
--     @renderArea.offset.y@ /must/ be greater than or equal to 0
--
-- -   If the @pNext@ chain does not contain
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo'
--     or its @deviceRenderAreaCount@ member is equal to 0,
--     @renderArea.offset.x@ + @renderArea.offset.width@ /must/ be less
--     than or equal to 'Vulkan.Core10.Pass.FramebufferCreateInfo'::@width@
--     the @framebuffer@ was created with
--
-- -   If the @pNext@ chain does not contain
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo'
--     or its @deviceRenderAreaCount@ member is equal to 0,
--     @renderArea.offset.y@ + @renderArea.offset.height@ /must/ be less
--     than or equal to
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@height@ the
--     @framebuffer@ was created with
--
-- -   If the @pNext@ chain contains
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo',
--     the @offset.x@ member of each element of @pDeviceRenderAreas@ /must/
--     be greater than or equal to 0
--
-- -   If the @pNext@ chain contains
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo',
--     the @offset.y@ member of each element of @pDeviceRenderAreas@ /must/
--     be greater than or equal to 0
--
-- -   If the @pNext@ chain contains
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo',
--     @offset.x@ + @offset.width@ of each element of @pDeviceRenderAreas@
--     /must/ be less than or equal to
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@width@ the
--     @framebuffer@ was created with
--
-- -   If the @pNext@ chain contains
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo',
--     @offset.y@ + @offset.height@ of each element of @pDeviceRenderAreas@
--     /must/ be less than or equal to
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@height@ the
--     @framebuffer@ was created with
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that did
--     not include
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     and the @pNext@ chain includes a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure, its @attachmentCount@ /must/ be zero
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     the @attachmentCount@ of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be equal to the value
--     of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@attachmentImageInfoCount@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ have been created on
--     the same 'Vulkan.Core10.Handles.Device' as @framebuffer@ and
--     @renderPass@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a value
--     of 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ equal to the
--     @flags@ member of the corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a value
--     of 'Vulkan.Core10.Image.ImageCreateInfo'::@usage@ equal to the
--     @usage@ member of the corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' with a width equal to the @width@
--     member of the corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' with a height equal to the
--     @height@ member of the corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a value
--     of
--     'Vulkan.Core10.ImageView.ImageViewCreateInfo'::@subresourceRange.layerCount@
--     equal to the @layerCount@ member of the corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a value
--     of
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@viewFormatCount@
--     equal to the @viewFormatCount@ member of the corresponding element
--     of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a set of
--     elements in
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@pViewFormats@
--     equal to the set of elements in the @pViewFormats@ member of the
--     corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachments@
--     used to create @framebuffer@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a value
--     of 'Vulkan.Core10.ImageView.ImageViewCreateInfo'::@format@ equal to
--     the corresponding value of
--     'Vulkan.Core10.Pass.AttachmentDescription'::@format@ in @renderPass@
--
-- -   If @framebuffer@ was created with a
--     'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ value that
--     included
--     'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT',
--     each element of the @pAttachments@ member of a
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'
--     structure included in the @pNext@ chain /must/ be a
--     'Vulkan.Core10.Handles.ImageView' of an image created with a value
--     of 'Vulkan.Core10.Image.ImageCreateInfo'::@samples@ equal to the
--     corresponding value of
--     'Vulkan.Core10.Pass.AttachmentDescription'::@samples@ in
--     @renderPass@
--
-- -   If the @pNext@ chain includes
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM',
--     @renderArea.offset@ /must/ equal (0,0)
--
-- -   If the @pNext@ chain includes
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM',
--     @renderArea.extent@ transformed by
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'::@transform@
--     /must/ equal the @framebuffer@ dimensions
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo',
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo',
--     'Vulkan.Extensions.VK_EXT_sample_locations.RenderPassSampleLocationsBeginInfoEXT',
--     or
--     'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @renderPass@ /must/ be a valid 'Vulkan.Core10.Handles.RenderPass'
--     handle
--
-- -   @framebuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Framebuffer'
--     handle
--
-- -   If @clearValueCount@ is not @0@, @pClearValues@ /must/ be a valid
--     pointer to an array of @clearValueCount@ 'ClearValue' unions
--
-- -   Both of @framebuffer@, and @renderPass@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'ClearValue', 'Vulkan.Core10.Handles.Framebuffer',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D',
-- 'Vulkan.Core10.Handles.RenderPass',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'cmdBeginRenderPass',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.cmdBeginRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdBeginRenderPass2KHR'
data RenderPassBeginInfo (es :: [Type]) = RenderPassBeginInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    RenderPassBeginInfo es -> Chain es
next :: Chain es
  , -- | @renderPass@ is the render pass to begin an instance of.
    RenderPassBeginInfo es -> RenderPass
renderPass :: RenderPass
  , -- | @framebuffer@ is the framebuffer containing the attachments that are
    -- used with the render pass.
    RenderPassBeginInfo es -> Framebuffer
framebuffer :: Framebuffer
  , -- | @renderArea@ is the render area that is affected by the render pass
    -- instance, and is described in more detail below.
    RenderPassBeginInfo es -> Rect2D
renderArea :: Rect2D
  , -- | @pClearValues@ is a pointer to an array of @clearValueCount@
    -- 'ClearValue' structures that contains clear values for each attachment,
    -- if the attachment uses a @loadOp@ value of
    -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' or if
    -- the attachment has a depth\/stencil format and uses a @stencilLoadOp@
    -- value of
    -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR'. The
    -- array is indexed by attachment number. Only elements corresponding to
    -- cleared attachments are used. Other elements of @pClearValues@ are
    -- ignored.
    RenderPassBeginInfo es -> Vector ClearValue
clearValues :: Vector ClearValue
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassBeginInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (RenderPassBeginInfo es)

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

instance (Extendss RenderPassBeginInfo es, PokeChain es) => ToCStruct (RenderPassBeginInfo es) where
  withCStruct :: RenderPassBeginInfo es
-> (Ptr (RenderPassBeginInfo es) -> IO b) -> IO b
withCStruct x :: RenderPassBeginInfo es
x f :: Ptr (RenderPassBeginInfo es) -> IO b
f = Int -> Int -> (Ptr (RenderPassBeginInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr (RenderPassBeginInfo es) -> IO b) -> IO b)
-> (Ptr (RenderPassBeginInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (RenderPassBeginInfo es)
p -> Ptr (RenderPassBeginInfo es)
-> RenderPassBeginInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (RenderPassBeginInfo es)
p RenderPassBeginInfo es
x (Ptr (RenderPassBeginInfo es) -> IO b
f Ptr (RenderPassBeginInfo es)
p)
  pokeCStruct :: Ptr (RenderPassBeginInfo es)
-> RenderPassBeginInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (RenderPassBeginInfo es)
p RenderPassBeginInfo{..} 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 (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO)
    "data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr RenderPass -> RenderPass -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RenderPass)) (RenderPass
renderPass)
    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 Framebuffer -> Framebuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr Framebuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Framebuffer)) (Framebuffer
framebuffer)
    ((() -> 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
$ ("pScissors" ::: Ptr Rect2D) -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> "pScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Rect2D)) (Rect2D
renderArea) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> 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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ClearValue -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ClearValue -> Int) -> Vector ClearValue -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ClearValue
clearValues)) :: Word32))
    Ptr ClearValue
pPClearValues' <- ((Ptr ClearValue -> IO b) -> IO b) -> ContT b IO (Ptr ClearValue)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ClearValue -> IO b) -> IO b) -> ContT b IO (Ptr ClearValue))
-> ((Ptr ClearValue -> IO b) -> IO b)
-> ContT b IO (Ptr ClearValue)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ClearValue -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ClearValue ((Vector ClearValue -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ClearValue
clearValues)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> ClearValue -> ContT b IO ())
-> Vector ClearValue -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ClearValue
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 ClearValue -> ClearValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ClearValue
pPClearValues' Ptr ClearValue -> Int -> Ptr ClearValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ClearValue) (ClearValue
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 ClearValue
clearValues)
    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 ClearValue) -> Ptr ClearValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr (Ptr ClearValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr ClearValue))) (Ptr ClearValue
pPClearValues')
    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 (RenderPassBeginInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (RenderPassBeginInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO)
    "data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr RenderPass -> RenderPass -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RenderPass)) (RenderPass
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Framebuffer -> Framebuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr Framebuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Framebuffer)) (Framebuffer
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pScissors" ::: Ptr Rect2D) -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> "pScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Rect2D)) (Rect2D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    Ptr ClearValue
pPClearValues' <- ((Ptr ClearValue -> IO b) -> IO b) -> ContT b IO (Ptr ClearValue)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ClearValue -> IO b) -> IO b) -> ContT b IO (Ptr ClearValue))
-> ((Ptr ClearValue -> IO b) -> IO b)
-> ContT b IO (Ptr ClearValue)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ClearValue -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ClearValue ((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 -> ClearValue -> ContT b IO ())
-> Vector ClearValue -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ClearValue
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 ClearValue -> ClearValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ClearValue
pPClearValues' Ptr ClearValue -> Int -> Ptr ClearValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ClearValue) (ClearValue
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 ClearValue
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 ClearValue) -> Ptr ClearValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassBeginInfo es)
p Ptr (RenderPassBeginInfo es) -> Int -> Ptr (Ptr ClearValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr ClearValue))) (Ptr ClearValue
pPClearValues')
    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 es ~ '[] => Zero (RenderPassBeginInfo es) where
  zero :: RenderPassBeginInfo es
zero = Chain es
-> RenderPass
-> Framebuffer
-> Rect2D
-> Vector ClearValue
-> RenderPassBeginInfo es
forall (es :: [*]).
Chain es
-> RenderPass
-> Framebuffer
-> Rect2D
-> Vector ClearValue
-> RenderPassBeginInfo es
RenderPassBeginInfo
           ()
           RenderPass
forall a. Zero a => a
zero
           Framebuffer
forall a. Zero a => a
zero
           Rect2D
forall a. Zero a => a
zero
           Vector ClearValue
forall a. Monoid a => a
mempty


-- | VkClearDepthStencilValue - Structure specifying a clear depth stencil
-- value
--
-- == Valid Usage
--
-- -   Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled
--     @depth@ /must/ be between @0.0@ and @1.0@, inclusive
--
-- = See Also
--
-- 'ClearValue', 'cmdClearDepthStencilImage'
data ClearDepthStencilValue = ClearDepthStencilValue
  { -- | @depth@ is the clear value for the depth aspect of the depth\/stencil
    -- attachment. It is a floating-point value which is automatically
    -- converted to the attachment’s format.
    ClearDepthStencilValue -> "lineWidth" ::: Float
depth :: Float
  , -- | @stencil@ is the clear value for the stencil aspect of the
    -- depth\/stencil attachment. It is a 32-bit integer value which is
    -- converted to the attachment’s format by taking the appropriate number of
    -- LSBs.
    ClearDepthStencilValue -> "firstViewport" ::: Word32
stencil :: Word32
  }
  deriving (Typeable, ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
(ClearDepthStencilValue -> ClearDepthStencilValue -> Bool)
-> (ClearDepthStencilValue -> ClearDepthStencilValue -> Bool)
-> Eq ClearDepthStencilValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
$c/= :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
== :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
$c== :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ClearDepthStencilValue)
#endif
deriving instance Show ClearDepthStencilValue

instance ToCStruct ClearDepthStencilValue where
  withCStruct :: ClearDepthStencilValue
-> (("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b)
-> IO b
withCStruct x :: ClearDepthStencilValue
x f :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b
f = Int
-> Int
-> (("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b)
 -> IO b)
-> (("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pDepthStencil" ::: Ptr ClearDepthStencilValue
p -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> ClearDepthStencilValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pDepthStencil" ::: Ptr ClearDepthStencilValue
p ClearDepthStencilValue
x (("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b
f "pDepthStencil" ::: Ptr ClearDepthStencilValue
p)
  pokeCStruct :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> ClearDepthStencilValue -> IO b -> IO b
pokeCStruct p :: "pDepthStencil" ::: Ptr ClearDepthStencilValue
p ClearDepthStencilValue{..} f :: IO b
f = do
    Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue
p ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
depth))
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue
p ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("firstViewport" ::: Word32
stencil)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b -> IO b
pokeZeroCStruct p :: "pDepthStencil" ::: Ptr ClearDepthStencilValue
p f :: IO b
f = do
    Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue
p ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
forall a. Zero a => a
zero))
    ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue
p ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ClearDepthStencilValue where
  peekCStruct :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> IO ClearDepthStencilValue
peekCStruct p :: "pDepthStencil" ::: Ptr ClearDepthStencilValue
p = do
    "lineWidth" ::: CFloat
depth <- Ptr ("lineWidth" ::: CFloat) -> IO ("lineWidth" ::: CFloat)
forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pDepthStencil" ::: Ptr ClearDepthStencilValue
p ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat))
    "firstViewport" ::: Word32
stencil <- ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pDepthStencil" ::: Ptr ClearDepthStencilValue
p ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    ClearDepthStencilValue -> IO ClearDepthStencilValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ClearDepthStencilValue -> IO ClearDepthStencilValue)
-> ClearDepthStencilValue -> IO ClearDepthStencilValue
forall a b. (a -> b) -> a -> b
$ ("lineWidth" ::: Float)
-> ("firstViewport" ::: Word32) -> ClearDepthStencilValue
ClearDepthStencilValue
             ((\(CFloat a :: "lineWidth" ::: Float
a) -> "lineWidth" ::: Float
a) "lineWidth" ::: CFloat
depth) "firstViewport" ::: Word32
stencil

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

instance Zero ClearDepthStencilValue where
  zero :: ClearDepthStencilValue
zero = ("lineWidth" ::: Float)
-> ("firstViewport" ::: Word32) -> ClearDepthStencilValue
ClearDepthStencilValue
           "lineWidth" ::: Float
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero


-- | VkClearAttachment - Structure specifying a clear attachment
--
-- = Description
--
-- No memory barriers are needed between 'cmdClearAttachments' and
-- preceding or subsequent draw or attachment clear commands in the same
-- subpass.
--
-- The 'cmdClearAttachments' command is not affected by the bound pipeline
-- state.
--
-- Attachments /can/ also be cleared at the beginning of a render pass
-- instance by setting @loadOp@ (or @stencilLoadOp@) of
-- 'Vulkan.Core10.Pass.AttachmentDescription' to
-- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', as
-- described for 'Vulkan.Core10.Pass.createRenderPass'.
--
-- == Valid Usage
--
-- -   If @aspectMask@ includes
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', it
--     /must/ not include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--
-- -   @aspectMask@ /must/ not include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT'
--
-- -   @aspectMask@ /must/ not include
--     @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index @i@
--
-- -   @clearValue@ /must/ be a valid 'ClearValue' union
--
-- == Valid Usage (Implicit)
--
-- -   @aspectMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values
--
-- -   @aspectMask@ /must/ not be @0@
--
-- = See Also
--
-- 'ClearValue',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags',
-- 'cmdClearAttachments'
data ClearAttachment = ClearAttachment
  { -- | @aspectMask@ is a mask selecting the color, depth and\/or stencil
    -- aspects of the attachment to be cleared.
    ClearAttachment -> ImageAspectFlags
aspectMask :: ImageAspectFlags
  , -- | @colorAttachment@ is only meaningful if
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' is set
    -- in @aspectMask@, in which case it is an index to the @pColorAttachments@
    -- array in the 'Vulkan.Core10.Pass.SubpassDescription' structure of the
    -- current subpass which selects the color attachment to clear.
    ClearAttachment -> "firstViewport" ::: Word32
colorAttachment :: Word32
  , -- | @clearValue@ is the color or depth\/stencil value to clear the
    -- attachment to, as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears-values Clear Values>
    -- below.
    ClearAttachment -> ClearValue
clearValue :: ClearValue
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ClearAttachment)
#endif
deriving instance Show ClearAttachment

instance ToCStruct ClearAttachment where
  withCStruct :: ClearAttachment
-> (("pAttachments" ::: Ptr ClearAttachment) -> IO b) -> IO b
withCStruct x :: ClearAttachment
x f :: ("pAttachments" ::: Ptr ClearAttachment) -> IO b
f = Int
-> Int
-> (("pAttachments" ::: Ptr ClearAttachment) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 4 ((("pAttachments" ::: Ptr ClearAttachment) -> IO b) -> IO b)
-> (("pAttachments" ::: Ptr ClearAttachment) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pAttachments" ::: Ptr ClearAttachment
p -> ("pAttachments" ::: Ptr ClearAttachment)
-> ClearAttachment -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pAttachments" ::: Ptr ClearAttachment
p ClearAttachment
x (("pAttachments" ::: Ptr ClearAttachment) -> IO b
f "pAttachments" ::: Ptr ClearAttachment
p)
  pokeCStruct :: ("pAttachments" ::: Ptr ClearAttachment)
-> ClearAttachment -> IO b -> IO b
pokeCStruct p :: "pAttachments" ::: Ptr ClearAttachment
p ClearAttachment{..} 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 ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAttachments" ::: Ptr ClearAttachment
p ("pAttachments" ::: Ptr ClearAttachment)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
    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
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAttachments" ::: Ptr ClearAttachment
p ("pAttachments" ::: Ptr ClearAttachment)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("firstViewport" ::: Word32
colorAttachment)
    ((() -> 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 ClearValue -> ClearValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pAttachments" ::: Ptr ClearAttachment
p ("pAttachments" ::: Ptr ClearAttachment) -> Int -> Ptr ClearValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr ClearValue)) (ClearValue
clearValue) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pAttachments" ::: Ptr ClearAttachment) -> IO b -> IO b
pokeZeroCStruct p :: "pAttachments" ::: Ptr ClearAttachment
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 ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAttachments" ::: Ptr ClearAttachment
p ("pAttachments" ::: Ptr ClearAttachment)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAttachments" ::: Ptr ClearAttachment
p ("pAttachments" ::: Ptr ClearAttachment)
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("firstViewport" ::: Word32
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ClearValue -> ClearValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pAttachments" ::: Ptr ClearAttachment
p ("pAttachments" ::: Ptr ClearAttachment) -> Int -> Ptr ClearValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr ClearValue)) (ClearValue
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance Zero ClearAttachment where
  zero :: ClearAttachment
zero = ImageAspectFlags
-> ("firstViewport" ::: Word32) -> ClearValue -> ClearAttachment
ClearAttachment
           ImageAspectFlags
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           ClearValue
forall a. Zero a => a
zero


data ClearColorValue
  = Float32 ((Float, Float, Float, Float))
  | Int32 ((Int32, Int32, Int32, Int32))
  | Uint32 ((Word32, Word32, Word32, Word32))
  deriving (Int -> ClearColorValue -> ShowS
[ClearColorValue] -> ShowS
ClearColorValue -> String
(Int -> ClearColorValue -> ShowS)
-> (ClearColorValue -> String)
-> ([ClearColorValue] -> ShowS)
-> Show ClearColorValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearColorValue] -> ShowS
$cshowList :: [ClearColorValue] -> ShowS
show :: ClearColorValue -> String
$cshow :: ClearColorValue -> String
showsPrec :: Int -> ClearColorValue -> ShowS
$cshowsPrec :: Int -> ClearColorValue -> ShowS
Show)

instance ToCStruct ClearColorValue where
  withCStruct :: ClearColorValue
-> (("pColor" ::: Ptr ClearColorValue) -> IO b) -> IO b
withCStruct x :: ClearColorValue
x f :: ("pColor" ::: Ptr ClearColorValue) -> IO b
f = Int -> Int -> (("pColor" ::: Ptr ClearColorValue) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((("pColor" ::: Ptr ClearColorValue) -> IO b) -> IO b)
-> (("pColor" ::: Ptr ClearColorValue) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pColor" ::: Ptr ClearColorValue
p -> ("pColor" ::: Ptr ClearColorValue)
-> ClearColorValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pColor" ::: Ptr ClearColorValue
p ClearColorValue
x (("pColor" ::: Ptr ClearColorValue) -> IO b
f "pColor" ::: Ptr ClearColorValue
p)
  pokeCStruct :: Ptr ClearColorValue -> ClearColorValue -> IO a -> IO a
  pokeCStruct :: ("pColor" ::: Ptr ClearColorValue)
-> ClearColorValue -> IO a -> IO a
pokeCStruct p :: "pColor" ::: Ptr ClearColorValue
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (ClearColorValue -> (() -> IO a) -> IO a)
-> ClearColorValue
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (ClearColorValue -> ContT a IO ())
-> ClearColorValue
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Float32 v :: "blendConstants"
::: ("lineWidth" ::: Float, "lineWidth" ::: Float,
     "lineWidth" ::: Float, "lineWidth" ::: Float)
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ do
      let pFloat32 :: Ptr ("lineWidth" ::: CFloat)
pFloat32 = ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))
-> Ptr ("lineWidth" ::: CFloat)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pColor" ::: Ptr ClearColorValue)
-> "blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))
forall a b. Ptr a -> Ptr b
castPtr @_ @(FixedArray 4 CFloat) "pColor" ::: Ptr ClearColorValue
p)
      case ("blendConstants"
::: ("lineWidth" ::: Float, "lineWidth" ::: Float,
     "lineWidth" ::: Float, "lineWidth" ::: Float)
v) of
        (e0 :: "lineWidth" ::: Float
e0, e1 :: "lineWidth" ::: Float
e1, e2 :: "lineWidth" ::: Float
e2, e3 :: "lineWidth" ::: Float
e3) -> do
          Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pFloat32 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e0))
          Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pFloat32 Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e1))
          Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pFloat32 Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e2))
          Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lineWidth" ::: CFloat)
pFloat32 Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat
CFloat ("lineWidth" ::: Float
e3))
    Int32 v :: ("vertexOffset" ::: Int32, "vertexOffset" ::: Int32,
 "vertexOffset" ::: Int32, "vertexOffset" ::: Int32)
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ do
      let pInt32 :: Ptr ("vertexOffset" ::: Int32)
pInt32 = Ptr (FixedArray 4 ("vertexOffset" ::: Int32))
-> Ptr ("vertexOffset" ::: Int32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pColor" ::: Ptr ClearColorValue)
-> Ptr (FixedArray 4 ("vertexOffset" ::: Int32))
forall a b. Ptr a -> Ptr b
castPtr @_ @(FixedArray 4 Int32) "pColor" ::: Ptr ClearColorValue
p)
      case (("vertexOffset" ::: Int32, "vertexOffset" ::: Int32,
 "vertexOffset" ::: Int32, "vertexOffset" ::: Int32)
v) of
        (e0 :: "vertexOffset" ::: Int32
e0, e1 :: "vertexOffset" ::: Int32
e1, e2 :: "vertexOffset" ::: Int32
e2, e3 :: "vertexOffset" ::: Int32
e3) -> do
          Ptr ("vertexOffset" ::: Int32)
-> ("vertexOffset" ::: Int32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("vertexOffset" ::: Int32)
pInt32 :: Ptr Int32) ("vertexOffset" ::: Int32
e0)
          Ptr ("vertexOffset" ::: Int32)
-> ("vertexOffset" ::: Int32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("vertexOffset" ::: Int32)
pInt32 Ptr ("vertexOffset" ::: Int32)
-> Int -> Ptr ("vertexOffset" ::: Int32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32) ("vertexOffset" ::: Int32
e1)
          Ptr ("vertexOffset" ::: Int32)
-> ("vertexOffset" ::: Int32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("vertexOffset" ::: Int32)
pInt32 Ptr ("vertexOffset" ::: Int32)
-> Int -> Ptr ("vertexOffset" ::: Int32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Int32) ("vertexOffset" ::: Int32
e2)
          Ptr ("vertexOffset" ::: Int32)
-> ("vertexOffset" ::: Int32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("vertexOffset" ::: Int32)
pInt32 Ptr ("vertexOffset" ::: Int32)
-> Int -> Ptr ("vertexOffset" ::: Int32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Int32) ("vertexOffset" ::: Int32
e3)
    Uint32 v :: ("firstViewport" ::: Word32, "firstViewport" ::: Word32,
 "firstViewport" ::: Word32, "firstViewport" ::: Word32)
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ do
      let pUint32 :: "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pUint32 = Ptr (FixedArray 4 ("firstViewport" ::: Word32))
-> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pColor" ::: Ptr ClearColorValue)
-> Ptr (FixedArray 4 ("firstViewport" ::: Word32))
forall a b. Ptr a -> Ptr b
castPtr @_ @(FixedArray 4 Word32) "pColor" ::: Ptr ClearColorValue
p)
      case (("firstViewport" ::: Word32, "firstViewport" ::: Word32,
 "firstViewport" ::: Word32, "firstViewport" ::: Word32)
v) of
        (e0 :: "firstViewport" ::: Word32
e0, e1 :: "firstViewport" ::: Word32
e1, e2 :: "firstViewport" ::: Word32
e2, e3 :: "firstViewport" ::: Word32
e3) -> do
          ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pUint32 :: Ptr Word32) ("firstViewport" ::: Word32
e0)
          ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pUint32 ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) ("firstViewport" ::: Word32
e1)
          ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pUint32 ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) ("firstViewport" ::: Word32
e2)
          ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
pUint32 ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))
-> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32) ("firstViewport" ::: Word32
e3)
  pokeZeroCStruct :: Ptr ClearColorValue -> IO b -> IO b
  pokeZeroCStruct :: ("pColor" ::: Ptr ClearColorValue) -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4

instance Zero ClearColorValue where
  zero :: ClearColorValue
zero = ("blendConstants"
 ::: ("lineWidth" ::: Float, "lineWidth" ::: Float,
      "lineWidth" ::: Float, "lineWidth" ::: Float))
-> ClearColorValue
Float32 ("lineWidth" ::: Float
forall a. Zero a => a
zero, "lineWidth" ::: Float
forall a. Zero a => a
zero, "lineWidth" ::: Float
forall a. Zero a => a
zero, "lineWidth" ::: Float
forall a. Zero a => a
zero)


data ClearValue
  = Color ClearColorValue
  | DepthStencil ClearDepthStencilValue
  deriving (Int -> ClearValue -> ShowS
[ClearValue] -> ShowS
ClearValue -> String
(Int -> ClearValue -> ShowS)
-> (ClearValue -> String)
-> ([ClearValue] -> ShowS)
-> Show ClearValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearValue] -> ShowS
$cshowList :: [ClearValue] -> ShowS
show :: ClearValue -> String
$cshow :: ClearValue -> String
showsPrec :: Int -> ClearValue -> ShowS
$cshowsPrec :: Int -> ClearValue -> ShowS
Show)

instance ToCStruct ClearValue where
  withCStruct :: ClearValue -> (Ptr ClearValue -> IO b) -> IO b
withCStruct x :: ClearValue
x f :: Ptr ClearValue -> IO b
f = Int -> Int -> (Ptr ClearValue -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr ClearValue -> IO b) -> IO b)
-> (Ptr ClearValue -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ClearValue
p -> Ptr ClearValue -> ClearValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ClearValue
p ClearValue
x (Ptr ClearValue -> IO b
f Ptr ClearValue
p)
  pokeCStruct :: Ptr ClearValue -> ClearValue -> IO a -> IO a
  pokeCStruct :: Ptr ClearValue -> ClearValue -> IO a -> IO a
pokeCStruct p :: Ptr ClearValue
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (ClearValue -> (() -> IO a) -> IO a)
-> ClearValue
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (ClearValue -> ContT a IO ())
-> ClearValue
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Color v :: ClearColorValue
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ ("pColor" ::: Ptr ClearColorValue)
-> ClearColorValue -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ClearValue -> "pColor" ::: Ptr ClearColorValue
forall a b. Ptr a -> Ptr b
castPtr @_ @ClearColorValue Ptr ClearValue
p) (ClearColorValue
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
    DepthStencil v :: ClearDepthStencilValue
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ ("pDepthStencil" ::: Ptr ClearDepthStencilValue)
-> ClearDepthStencilValue -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ClearValue -> "pDepthStencil" ::: Ptr ClearDepthStencilValue
forall a b. Ptr a -> Ptr b
castPtr @_ @ClearDepthStencilValue Ptr ClearValue
p) (ClearDepthStencilValue
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
  pokeZeroCStruct :: Ptr ClearValue -> IO b -> IO b
  pokeZeroCStruct :: Ptr ClearValue -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4

instance Zero ClearValue where
  zero :: ClearValue
zero = ClearColorValue -> ClearValue
Color ClearColorValue
forall a. Zero a => a
zero