{-# language CPP #-} -- No documentation found for Chapter "CommandBufferBuilding" 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 Vulkan.Internal.Utils (traceAroundEvent) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Data.Typeable (eqT) import Foreign.Marshal.Alloc (allocaBytes) 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 Data.Coerce (coerce) 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 Vulkan.CStruct (FromCStruct) import Vulkan.CStruct (FromCStruct(..)) import Vulkan.CStruct (ToCStruct) import Vulkan.CStruct (ToCStruct(..)) import Vulkan.Zero (Zero(..)) import Control.Monad.IO.Class (MonadIO) import Data.Type.Equality ((:~:)(Refl)) import Data.Typeable (Typeable) import Foreign.C.Types (CFloat) 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(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.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 {-# SOURCE #-} Vulkan.Extensions.VK_QCOM_multiview_per_view_render_areas (MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM) 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.Core10.Pipeline (Viewport) 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, or until the -- pipeline bind point is disturbed by binding a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader object> -- as described in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects-pipeline-interaction Interaction with Pipelines>. -- Commands that do not interact with the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-binding given pipeline> -- type /must/ not be affected by the pipeline state. -- -- == Valid Usage -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-00777# 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 -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-00778# 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 -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-00779# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE', -- @pipeline@ /must/ be a compute pipeline -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-00780# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS', -- @pipeline@ /must/ be a graphics pipeline -- -- - #VUID-vkCmdBindPipeline-pipeline-00781# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-variableMultisampleRate variableMultisampleRate> -- feature is not supported, @pipeline@ is a graphics pipeline, the -- current subpass -- <https://registry.khronos.org/vulkan/specs/1.3-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 -- -- - #VUID-vkCmdBindPipeline-variableSampleLocations-01525# 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 -- -- - #VUID-vkCmdBindPipeline-None-02323# This command /must/ not be -- recorded when transform feedback is active -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-02391# 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 -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-02392# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR', -- @pipeline@ /must/ be a ray tracing pipeline -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-06721# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR', -- @commandBuffer@ /must/ not be a protected command buffer -- -- - #VUID-vkCmdBindPipeline-pipelineProtectedAccess-07408# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-pipelineProtectedAccess pipelineProtectedAccess> -- feature is enabled, and @commandBuffer@ is a protected command -- buffer, @pipeline@ /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_NO_PROTECTED_ACCESS_BIT_EXT' -- -- - #VUID-vkCmdBindPipeline-pipelineProtectedAccess-07409# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-pipelineProtectedAccess pipelineProtectedAccess> -- feature is enabled, and @commandBuffer@ is not a protected command -- buffer, @pipeline@ /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_PROTECTED_ACCESS_ONLY_BIT_EXT' -- -- - #VUID-vkCmdBindPipeline-pipeline-03382# @pipeline@ /must/ not have -- been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR' -- set -- -- - #VUID-vkCmdBindPipeline-commandBuffer-04808# If @commandBuffer@ is a -- secondary command buffer with -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@ -- enabled and @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS', -- then the @pipeline@ /must/ have been created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- or 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT', and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- or 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' enabled -- -- - #VUID-vkCmdBindPipeline-commandBuffer-04809# If @commandBuffer@ is a -- secondary command buffer with -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@ -- enabled and @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- and @pipeline@ was created with -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT' -- structure and its @discardRectangleCount@ member is not @0@, or the -- pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT' -- enabled, then the pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT' -- enabled -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-04881# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- and the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-provokingVertexModePerPipeline provokingVertexModePerPipeline> -- limit is 'Vulkan.Core10.FundamentalTypes.FALSE', then pipeline’s -- 'Vulkan.Extensions.VK_EXT_provoking_vertex.PipelineRasterizationProvokingVertexStateCreateInfoEXT'::@provokingVertexMode@ -- /must/ be the same as that of any other pipelines previously bound -- to this bind point within the current render pass instance, -- including any pipeline already bound when beginning the render pass -- instance -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-04949# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_SUBPASS_SHADING_HUAWEI', -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-04950# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_SUBPASS_SHADING_HUAWEI', -- @pipeline@ /must/ be a subpass shading pipeline -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-06653# If -- @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS', -- @pipeline@ /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR' -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdBindPipeline-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBindPipeline-pipelineBindPoint-parameter# -- @pipelineBindPoint@ /must/ be a valid -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- -- - #VUID-vkCmdBindPipeline-pipeline-parameter# @pipeline@ /must/ be a -- valid 'Vulkan.Core10.Handles.Pipeline' handle -- -- - #VUID-vkCmdBindPipeline-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBindPipeline-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - #VUID-vkCmdBindPipeline-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdBindPipeline-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> PipelineBindPoint -> Pipeline -> io () cmdBindPipeline CommandBuffer commandBuffer PipelineBindPoint pipelineBindPoint Pipeline pipeline = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds :: DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) vkCmdBindPipelinePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBindPipeline is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBindPipeline" (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO () vkCmdBindPipeline' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (PipelineBindPoint pipelineBindPoint) (Pipeline pipeline)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetViewport :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Viewport -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Viewport -> IO () -- | vkCmdSetViewport - Set the viewport dynamically for a command buffer -- -- = Description -- -- This command sets the viewport transformation parameters state for -- subsequent drawing commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@pViewports@ -- values used to create the currently active pipeline. -- -- 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 -- -- - #VUID-vkCmdSetViewport-firstViewport-01223# The sum of -- @firstViewport@ and @viewportCount@ /must/ be between @1@ and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@, -- inclusive -- -- - #VUID-vkCmdSetViewport-firstViewport-01224# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiViewport multiViewport> -- feature is not enabled, @firstViewport@ /must/ be @0@ -- -- - #VUID-vkCmdSetViewport-viewportCount-01225# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiViewport multiViewport> -- feature is not enabled, @viewportCount@ /must/ be @1@ -- -- - #VUID-vkCmdSetViewport-commandBuffer-04821# @commandBuffer@ /must/ -- not have -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@ -- enabled -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetViewport-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetViewport-pViewports-parameter# @pViewports@ /must/ be -- a valid pointer to an array of @viewportCount@ valid -- 'Vulkan.Core10.Pipeline.Viewport' structures -- -- - #VUID-vkCmdSetViewport-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetViewport-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetViewport-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdSetViewport-viewportCount-arraylength# @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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("firstViewport" ::: Word32) -> ("viewports" ::: Vector Viewport) -> io () cmdSetViewport CommandBuffer commandBuffer "firstViewport" ::: Word32 firstViewport "viewports" ::: Vector Viewport viewports = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetViewport is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Viewport ((forall a. Vector a -> Int Data.Vector.length ("viewports" ::: Vector Viewport viewports)) forall a. Num a => a -> a -> a * Int 24) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Viewport e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pViewports" ::: Ptr Viewport pPViewports forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Viewport) (Viewport e)) ("viewports" ::: Vector Viewport viewports) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetViewport" (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () vkCmdSetViewport' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 firstViewport) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("viewports" ::: Vector Viewport viewports)) :: Word32)) ("pViewports" ::: Ptr Viewport pPViewports)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetScissor :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO () -- | vkCmdSetScissor - Set scissor rectangles dynamically for 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 scissor rectangles for subsequent drawing commands -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@pScissors@ -- values used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetScissor-firstScissor-00592# The sum of @firstScissor@ -- and @scissorCount@ /must/ be between @1@ and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@, -- inclusive -- -- - #VUID-vkCmdSetScissor-firstScissor-00593# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiViewport multiViewport> -- feature is not enabled, @firstScissor@ /must/ be @0@ -- -- - #VUID-vkCmdSetScissor-scissorCount-00594# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiViewport multiViewport> -- feature is not enabled, @scissorCount@ /must/ be @1@ -- -- - #VUID-vkCmdSetScissor-x-00595# The @x@ and @y@ members of @offset@ -- member of any element of @pScissors@ /must/ be greater than or equal -- to @0@ -- -- - #VUID-vkCmdSetScissor-offset-00596# Evaluation of (@offset.x@ + -- @extent.width@) /must/ not cause a signed integer addition overflow -- for any element of @pScissors@ -- -- - #VUID-vkCmdSetScissor-offset-00597# Evaluation of (@offset.y@ + -- @extent.height@) /must/ not cause a signed integer addition overflow -- for any element of @pScissors@ -- -- - #VUID-vkCmdSetScissor-viewportScissor2D-04789# If this command is -- recorded in a secondary command buffer with -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@ -- enabled, then this function /must/ not be called -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetScissor-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetScissor-pScissors-parameter# @pScissors@ /must/ be a -- valid pointer to an array of @scissorCount@ -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures -- -- - #VUID-vkCmdSetScissor-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetScissor-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetScissor-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdSetScissor-scissorCount-arraylength# @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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("firstViewport" ::: Word32) -> ("scissors" ::: Vector Rect2D) -> io () cmdSetScissor CommandBuffer commandBuffer "firstViewport" ::: Word32 firstScissor "scissors" ::: Vector Rect2D scissors = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetScissor is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Rect2D ((forall a. Vector a -> Int Data.Vector.length ("scissors" ::: Vector Rect2D scissors)) forall a. Num a => a -> a -> a * Int 16) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Rect2D e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pScissors" ::: Ptr Rect2D pPScissors forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 16 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Rect2D) (Rect2D e)) ("scissors" ::: Vector Rect2D scissors) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetScissor" (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () vkCmdSetScissor' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 firstScissor) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("scissors" ::: Vector Rect2D scissors)) :: Word32)) ("pScissors" ::: Ptr Rect2D pPScissors)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetLineWidth :: FunPtr (Ptr CommandBuffer_T -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> IO () -- | vkCmdSetLineWidth - Set line width dynamically for a command buffer -- -- = Description -- -- This command sets the line width for subsequent drawing commands when -- drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@lineWidth@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetLineWidth-lineWidth-00788# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-wideLines wideLines> -- feature is not enabled, @lineWidth@ /must/ be @1.0@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetLineWidth-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetLineWidth-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetLineWidth-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetLineWidth-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("lineWidth" ::: Float) -> io () cmdSetLineWidth CommandBuffer commandBuffer "lineWidth" ::: Float lineWidth = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetLineWidthPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetLineWidth is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetLineWidth" (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetLineWidth' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float lineWidth))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthBias :: FunPtr (Ptr CommandBuffer_T -> CFloat -> CFloat -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> CFloat -> CFloat -> IO () -- | vkCmdSetDepthBias - Set depth bias factors and clamp dynamically for a -- command buffer -- -- = Description -- -- This command sets the depth bias parameters for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the corresponding -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@depthBiasConstantFactor@, -- @depthBiasClamp@, and @depthBiasSlopeFactor@ values used to create the -- currently active pipeline. -- -- Calling this function is equivalent to calling -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- without a -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.DepthBiasRepresentationInfoEXT' -- in the pNext chain of -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.DepthBiasInfoEXT'. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDepthBias-depthBiasClamp-00790# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-depthBiasClamp depthBiasClamp> -- feature is not enabled, @depthBiasClamp@ /must/ be @0.0@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDepthBias-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDepthBias-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDepthBias-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetDepthBias-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> io () cmdSetDepthBias CommandBuffer commandBuffer "lineWidth" ::: Float depthBiasConstantFactor "lineWidth" ::: Float depthBiasClamp "lineWidth" ::: Float depthBiasSlopeFactor = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBiasPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDepthBias is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDepthBias" (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))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- = Description -- -- This command sets blend constants for subsequent drawing commands when -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_BLEND_CONSTANTS' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'::@blendConstants@ -- values used to create the currently active pipeline. -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetBlendConstants-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetBlendConstants-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetBlendConstants-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetBlendConstants-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 -- Rc, Gc, Bc, and Ac components of the blend constant color used in -- blending, depending on the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#framebuffer-blendfactors blend factor>. ("blendConstants" ::: (Float, Float, Float, Float)) -> io () cmdSetBlendConstants :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("blendConstants" ::: ("lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float)) -> io () cmdSetBlendConstants CommandBuffer commandBuffer "blendConstants" ::: ("lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float) blendConstants = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) vkCmdSetBlendConstantsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetBlendConstants is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @(FixedArray 4 CFloat) Int 16 let pBlendConstants' :: Ptr ("lineWidth" ::: CFloat) pBlendConstants' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr "blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)) pBlendConstants forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ case ("blendConstants" ::: ("lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float) blendConstants) of ("lineWidth" ::: Float e0, "lineWidth" ::: Float e1, "lineWidth" ::: Float e2, "lineWidth" ::: Float e3) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e0)) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e1)) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e2)) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e3)) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetBlendConstants" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthBounds :: FunPtr (Ptr CommandBuffer_T -> CFloat -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> CFloat -> IO () -- | vkCmdSetDepthBounds - Set depth bounds range dynamically for a command -- buffer -- -- = Description -- -- This command sets the depth bounds range for subsequent drawing commands -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@minDepthBounds@ -- and -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@maxDepthBounds@ -- values used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDepthBounds-minDepthBounds-00600# If the -- @VK_EXT_depth_range_unrestricted@ extension is not enabled -- @minDepthBounds@ /must/ be between @0.0@ and @1.0@, inclusive -- -- - #VUID-vkCmdSetDepthBounds-maxDepthBounds-00601# If the -- @VK_EXT_depth_range_unrestricted@ extension is not enabled -- @maxDepthBounds@ /must/ be between @0.0@ and @1.0@, inclusive -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDepthBounds-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDepthBounds-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDepthBounds-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetDepthBounds-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> io () cmdSetDepthBounds CommandBuffer commandBuffer "lineWidth" ::: Float minDepthBounds "lineWidth" ::: Float maxDepthBounds = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBoundsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDepthBounds is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDepthBounds" (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))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilCompareMask :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO () -- | vkCmdSetStencilCompareMask - Set stencil compare mask dynamically for a -- command buffer -- -- = Description -- -- This command sets the stencil compare mask for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.StencilOpState'::@compareMask@ value used to -- create the currently active pipeline, for both front and back faces. -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetStencilCompareMask-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetStencilCompareMask-faceMask-parameter# @faceMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - #VUID-vkCmdSetStencilCompareMask-faceMask-requiredbitmask# -- @faceMask@ /must/ not be @0@ -- -- - #VUID-vkCmdSetStencilCompareMask-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetStencilCompareMask-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetStencilCompareMask-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> io () cmdSetStencilCompareMask CommandBuffer commandBuffer "faceMask" ::: StencilFaceFlags faceMask "firstViewport" ::: Word32 compareMask = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilCompareMaskPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetStencilCompareMask is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetStencilCompareMask" (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilCompareMask' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("firstViewport" ::: Word32 compareMask)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilWriteMask :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO () -- | vkCmdSetStencilWriteMask - Set stencil write mask dynamically for a -- command buffer -- -- = Description -- -- This command sets the stencil write mask for subsequent drawing commands -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the @writeMask@ value used to -- create the currently active pipeline, for both -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@front@ -- and 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@back@ -- faces. -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetStencilWriteMask-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetStencilWriteMask-faceMask-parameter# @faceMask@ /must/ -- be a valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - #VUID-vkCmdSetStencilWriteMask-faceMask-requiredbitmask# @faceMask@ -- /must/ not be @0@ -- -- - #VUID-vkCmdSetStencilWriteMask-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetStencilWriteMask-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetStencilWriteMask-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> io () cmdSetStencilWriteMask CommandBuffer commandBuffer "faceMask" ::: StencilFaceFlags faceMask "firstViewport" ::: Word32 writeMask = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilWriteMaskPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetStencilWriteMask is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetStencilWriteMask" (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilWriteMask' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("firstViewport" ::: Word32 writeMask)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilReference :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO () -- | vkCmdSetStencilReference - Set stencil reference value dynamically for a -- command buffer -- -- = Description -- -- This command sets the stencil reference value for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@reference@ -- value used to create the currently active pipeline, for both front and -- back faces. -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetStencilReference-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetStencilReference-faceMask-parameter# @faceMask@ /must/ -- be a valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - #VUID-vkCmdSetStencilReference-faceMask-requiredbitmask# @faceMask@ -- /must/ not be @0@ -- -- - #VUID-vkCmdSetStencilReference-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetStencilReference-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetStencilReference-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> io () cmdSetStencilReference CommandBuffer commandBuffer "faceMask" ::: StencilFaceFlags faceMask "firstViewport" ::: Word32 reference = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilReferencePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetStencilReference is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetStencilReference" (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilReference' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("firstViewport" ::: Word32 reference)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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' binds descriptor sets -- @pDescriptorSets@[0..@descriptorSetCount@-1] to set numbers -- [@firstSet@..@firstSet@+@descriptorSetCount@-1] for subsequent -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#pipelines-bindpoint-commands bound pipeline commands> -- set by @pipelineBindPoint@. Any bindings that were previously applied -- via these sets , or calls to -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT' -- or -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdBindDescriptorBufferEmbeddedSamplersEXT', -- 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://registry.khronos.org/vulkan/specs/1.3-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 drawing or dispatching -- 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. -- -- When consuming a descriptor, a descriptor is considered valid if the -- descriptor is not undefined as described by -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptor-set-initial-state descriptor set allocation>. -- If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is enabled, a null descriptor is also considered valid. A -- descriptor that was disturbed by -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility>, -- or was never bound by 'cmdBindDescriptorSets' is not considered valid. -- If a pipeline accesses a descriptor either statically or dynamically -- depending on the -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DescriptorBindingFlagBits', -- the consuming descriptor type in the pipeline /must/ match the -- 'Vulkan.Core10.Enums.DescriptorType.DescriptorType' in -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo' for the -- descriptor to be considered valid. If a descriptor is a mutable -- descriptor, the consuming descriptor type in the pipeline /must/ match -- the active descriptor type for the descriptor to be considered valid. -- -- Note -- -- Further validation may be carried out beyond validation for descriptor -- types, e.g. -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-input-validation Texel Input Validation>. -- -- 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#pipelines-bindpoint-commands bound pipeline commands> -- with that pipeline type, as defined in the -- <https://registry.khronos.org/vulkan/specs/1.3-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 -- -- - #VUID-vkCmdBindDescriptorSets-pDescriptorSets-00358# 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@ -- -- - #VUID-vkCmdBindDescriptorSets-dynamicOffsetCount-00359# -- @dynamicOffsetCount@ /must/ be equal to the total number of dynamic -- descriptors in @pDescriptorSets@ -- -- - #VUID-vkCmdBindDescriptorSets-firstSet-00360# The sum of @firstSet@ -- and @descriptorSetCount@ /must/ be less than or equal to -- 'Vulkan.Core10.PipelineLayout.PipelineLayoutCreateInfo'::@setLayoutCount@ -- provided when @layout@ was created -- -- - #VUID-vkCmdBindDescriptorSets-pipelineBindPoint-00361# -- @pipelineBindPoint@ /must/ be supported by the @commandBuffer@’s -- parent 'Vulkan.Core10.Handles.CommandPool'’s queue family -- -- - #VUID-vkCmdBindDescriptorSets-pDynamicOffsets-01971# 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@ -- -- - #VUID-vkCmdBindDescriptorSets-pDynamicOffsets-01972# 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@ -- -- - #VUID-vkCmdBindDescriptorSets-pDescriptorSets-01979# For each -- dynamic uniform or storage buffer binding in @pDescriptorSets@, the -- sum of the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#dynamic-effective-offset effective offset> -- and the range of the binding /must/ be less than or equal to the -- size of the buffer -- -- - #VUID-vkCmdBindDescriptorSets-pDescriptorSets-06715# For each -- dynamic uniform or storage buffer binding in @pDescriptorSets@, if -- the range was set with 'Vulkan.Core10.APIConstants.WHOLE_SIZE' then -- @pDynamicOffsets@ which corresponds to the descriptor binding /must/ -- be 0 -- -- - #VUID-vkCmdBindDescriptorSets-pDescriptorSets-04616# Each element of -- @pDescriptorSets@ /must/ not have been allocated from a -- 'Vulkan.Core10.Handles.DescriptorPool' with the -- 'Vulkan.Core10.Enums.DescriptorPoolCreateFlagBits.DESCRIPTOR_POOL_CREATE_HOST_ONLY_BIT_EXT' -- flag set -- -- - #VUID-vkCmdBindDescriptorSets-graphicsPipelineLibrary-06754# If -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-graphicsPipelineLibrary graphicsPipelineLibrary> -- is not enabled, each element of @pDescriptorSets@ /must/ be a valid -- 'Vulkan.Core10.Handles.DescriptorSet' -- -- - #VUID-vkCmdBindDescriptorSets-pDescriptorSets-08010# Each element of -- @pDescriptorSets@ /must/ have been allocated with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' which was not created -- with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdBindDescriptorSets-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBindDescriptorSets-pipelineBindPoint-parameter# -- @pipelineBindPoint@ /must/ be a valid -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- -- - #VUID-vkCmdBindDescriptorSets-layout-parameter# @layout@ /must/ be a -- valid 'Vulkan.Core10.Handles.PipelineLayout' handle -- -- - #VUID-vkCmdBindDescriptorSets-pDescriptorSets-parameter# -- @pDescriptorSets@ /must/ be a valid pointer to an array of -- @descriptorSetCount@ valid or -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- 'Vulkan.Core10.Handles.DescriptorSet' handles -- -- - #VUID-vkCmdBindDescriptorSets-pDynamicOffsets-parameter# If -- @dynamicOffsetCount@ is not @0@, @pDynamicOffsets@ /must/ be a valid -- pointer to an array of @dynamicOffsetCount@ @uint32_t@ values -- -- - #VUID-vkCmdBindDescriptorSets-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBindDescriptorSets-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - #VUID-vkCmdBindDescriptorSets-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdBindDescriptorSets-descriptorSetCount-arraylength# -- @descriptorSetCount@ /must/ be greater than @0@ -- -- - #VUID-vkCmdBindDescriptorSets-commonparent# Each of @commandBuffer@, -- @layout@, and the elements of @pDescriptorSets@ 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 bind to. ("descriptorSets" ::: Vector DescriptorSet) -> -- | @pDynamicOffsets@ is a pointer to an array of @uint32_t@ values -- specifying dynamic offsets. ("dynamicOffsets" ::: Vector Word32) -> io () cmdBindDescriptorSets :: forall (io :: * -> *). MonadIO io => CommandBuffer -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("descriptorSets" ::: Vector DescriptorSet) -> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> io () cmdBindDescriptorSets CommandBuffer commandBuffer PipelineBindPoint pipelineBindPoint PipelineLayout layout "firstViewport" ::: Word32 firstSet "descriptorSets" ::: Vector DescriptorSet descriptorSets "dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) vkCmdBindDescriptorSetsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBindDescriptorSets is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @DescriptorSet ((forall a. Vector a -> Int Data.Vector.length ("descriptorSets" ::: Vector DescriptorSet descriptorSets)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i DescriptorSet e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pDescriptorSets" ::: Ptr DescriptorSet pPDescriptorSets forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DescriptorSet) (DescriptorSet e)) ("descriptorSets" ::: Vector DescriptorSet descriptorSets) "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pPDynamicOffsets <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Word32 ((forall a. Vector a -> Int Data.Vector.length ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets)) forall a. Num a => a -> a -> a * Int 4) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i "firstViewport" ::: Word32 e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pPDynamicOffsets forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32) ("firstViewport" ::: Word32 e)) ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBindDescriptorSets" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("descriptorSets" ::: Vector DescriptorSet descriptorSets)) :: Word32)) ("pDescriptorSets" ::: Ptr DescriptorSet pPDescriptorSets) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets)) :: Word32)) ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pPDynamicOffsets)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdBindIndexBuffer-offset-08782# @offset@ /must/ be less -- than the size of @buffer@ -- -- - #VUID-vkCmdBindIndexBuffer-offset-08783# The sum of @offset@ and the -- base address of the range of 'Vulkan.Core10.Handles.DeviceMemory' -- object that is backing @buffer@, /must/ be a multiple of the size of -- the type indicated by @indexType@ -- -- - #VUID-vkCmdBindIndexBuffer-buffer-08784# @buffer@ /must/ have been -- created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDEX_BUFFER_BIT' -- flag -- -- - #VUID-vkCmdBindIndexBuffer-buffer-08785# If @buffer@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdBindIndexBuffer-indexType-08786# @indexType@ /must/ not -- be 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_NONE_KHR' -- -- - #VUID-vkCmdBindIndexBuffer-indexType-08787# 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) -- -- - #VUID-vkCmdBindIndexBuffer-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBindIndexBuffer-buffer-parameter# @buffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdBindIndexBuffer-indexType-parameter# @indexType@ /must/ -- be a valid 'Vulkan.Core10.Enums.IndexType.IndexType' value -- -- - #VUID-vkCmdBindIndexBuffer-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBindIndexBuffer-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBindIndexBuffer-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdBindIndexBuffer-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 the size of the indices. IndexType -> io () cmdBindIndexBuffer :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> io () cmdBindIndexBuffer CommandBuffer commandBuffer Buffer buffer "offset" ::: DeviceSize offset IndexType indexType = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) vkCmdBindIndexBufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBindIndexBuffer is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBindIndexBuffer" (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO () vkCmdBindIndexBuffer' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer buffer) ("offset" ::: DeviceSize offset) (IndexType indexType)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 drawing commands. If the -- <https://registry.khronos.org/vulkan/specs/1.3-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 -- -- - #VUID-vkCmdBindVertexBuffers-firstBinding-00624# @firstBinding@ -- /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@ -- -- - #VUID-vkCmdBindVertexBuffers-firstBinding-00625# The sum of -- @firstBinding@ and @bindingCount@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@ -- -- - #VUID-vkCmdBindVertexBuffers-pOffsets-00626# All elements of -- @pOffsets@ /must/ be less than the size of the corresponding element -- in @pBuffers@ -- -- - #VUID-vkCmdBindVertexBuffers-pBuffers-00627# All elements of -- @pBuffers@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_VERTEX_BUFFER_BIT' -- flag -- -- - #VUID-vkCmdBindVertexBuffers-pBuffers-00628# Each element of -- @pBuffers@ that is non-sparse /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdBindVertexBuffers-pBuffers-04001# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all elements of @pBuffers@ /must/ not be -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdBindVertexBuffers-pBuffers-04002# If an element of -- @pBuffers@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- corresponding element of @pOffsets@ /must/ be zero -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdBindVertexBuffers-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBindVertexBuffers-pBuffers-parameter# @pBuffers@ /must/ -- be a valid pointer to an array of @bindingCount@ valid or -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- 'Vulkan.Core10.Handles.Buffer' handles -- -- - #VUID-vkCmdBindVertexBuffers-pOffsets-parameter# @pOffsets@ /must/ -- be a valid pointer to an array of @bindingCount@ -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' values -- -- - #VUID-vkCmdBindVertexBuffers-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBindVertexBuffers-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBindVertexBuffers-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdBindVertexBuffers-bindingCount-arraylength# -- @bindingCount@ /must/ be greater than @0@ -- -- - #VUID-vkCmdBindVertexBuffers-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("firstViewport" ::: Word32) -> ("buffers" ::: Vector Buffer) -> ("offsets" ::: Vector ("offset" ::: DeviceSize)) -> io () cmdBindVertexBuffers CommandBuffer commandBuffer "firstViewport" ::: Word32 firstBinding "buffers" ::: Vector Buffer buffers "offsets" ::: Vector ("offset" ::: DeviceSize) offsets = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkCmdBindVertexBuffersPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBindVertexBuffers is null" forall a. Maybe a Nothing 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 = forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("buffers" ::: Vector Buffer buffers) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless ((forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("offsets" ::: Vector ("offset" ::: DeviceSize) offsets)) forall a. Eq a => a -> a -> Bool == Int pBuffersLength) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "pOffsets and pBuffers must have the same length" forall a. Maybe a Nothing forall a. Maybe a Nothing "pBuffers" ::: Ptr Buffer pPBuffers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Buffer ((forall a. Vector a -> Int Data.Vector.length ("buffers" ::: Vector Buffer buffers)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Buffer e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pBuffers" ::: Ptr Buffer pPBuffers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Buffer) (Buffer e)) ("buffers" ::: Vector Buffer buffers) "pOffsets" ::: Ptr ("offset" ::: DeviceSize) pPOffsets <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @DeviceSize ((forall a. Vector a -> Int Data.Vector.length ("offsets" ::: Vector ("offset" ::: DeviceSize) offsets)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i "offset" ::: DeviceSize e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pOffsets" ::: Ptr ("offset" ::: DeviceSize) pPOffsets forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DeviceSize) ("offset" ::: DeviceSize e)) ("offsets" ::: Vector ("offset" ::: DeviceSize) offsets) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBindVertexBuffers" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral Int pBuffersLength :: Word32)) ("pBuffers" ::: Ptr Buffer pPBuffers) ("pOffsets" ::: Ptr ("offset" ::: DeviceSize) pPOffsets)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdDraw-magFilter-04553# 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' -- -- - #VUID-vkCmdDraw-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_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' -- -- - #VUID-vkCmdDraw-None-06479# If a 'Vulkan.Core10.Handles.ImageView' -- is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDraw-None-02691# 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' -- -- - #VUID-vkCmdDraw-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDraw-None-02692# If a 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDraw-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDraw-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDraw-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDraw-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDraw-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDraw-flags-02696# 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' -- -- - #VUID-vkCmdDraw-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDraw-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDraw-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDraw-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDraw-None-08600# For each set /n/ that is statically used -- by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDraw-None-08601# For each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDraw-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDraw-None-08114# 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 and the bound -- 'Vulkan.Core10.Handles.Pipeline' was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08115# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via 'cmdBindDescriptorSets', the bound -- 'Vulkan.Core10.Handles.Pipeline' /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08116# Descriptors in bound descriptor buffers, -- specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08604# Descriptors in bound descriptor buffers, -- specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDraw-None-08117# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08119# If a descriptor is dynamically used with -- a 'Vulkan.Core10.Handles.Pipeline' created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDraw-None-08605# If a descriptor is dynamically used with -- a 'Vulkan.Extensions.Handles.ShaderEXT' created with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' that was created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDraw-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDraw-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDraw-None-08608# If a pipeline is bound to the pipeline -- bind point used by this command, 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 -- -- - #VUID-vkCmdDraw-None-08609# If the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDraw-None-08610# If the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDraw-None-08611# If the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDraw-uniformBuffers-06935# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a uniform buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDraw-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDraw-storageBuffers-06936# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a storage buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDraw-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDraw-commandBuffer-02707# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDraw-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDraw-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDraw-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDraw-format-07753# If a 'Vulkan.Core10.Handles.ImageView' -- is accessed as a result of this command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDraw-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' 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 -- -- - #VUID-vkCmdDraw-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDraw-OpImageWrite-04469# 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 -- buffer view’s format -- -- - #VUID-vkCmdDraw-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDraw-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDraw-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDraw-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDraw-sparseImageInt64Atomics-04474# 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 -- -- - #VUID-vkCmdDraw-sparseImageInt64Atomics-04475# 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 -- -- - #VUID-vkCmdDraw-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDraw-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageWeightedSampleQCOM-06978# If any command -- other than @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ not have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDraw-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDraw-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDraw-None-07288# Any shader invocation executed by this -- command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDraw-renderPass-02684# 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' -- -- - #VUID-vkCmdDraw-subpass-02685# 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' -- -- - #VUID-vkCmdDraw-None-07748# If any shader statically accesses an -- input attachment, a valid descriptor /must/ be bound to the pipeline -- via a descriptor set -- -- - #VUID-vkCmdDraw-OpTypeImage-07468# If any shader executed by this -- pipeline accesses an @OpTypeImage@ variable with a @Dim@ operand of -- @SubpassData@, it /must/ be decorated with an @InputAttachmentIndex@ -- that corresponds to a valid input attachment in the current subpass -- -- - #VUID-vkCmdDraw-None-07469# Input attachment views accessed in a -- subpass /must/ be created with the same -- 'Vulkan.Core10.Enums.Format.Format' as the corresponding subpass -- definition, and be created with a 'Vulkan.Core10.Handles.ImageView' -- that is compatible with the attachment referenced by the subpass\' -- @pInputAttachments@[@InputAttachmentIndex@] in the currently bound -- 'Vulkan.Core10.Handles.Framebuffer' as specified by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#compatibility-inputattachment Fragment Input Attachment Compatibility> -- -- - #VUID-vkCmdDraw-None-06537# Memory backing image subresources used -- as attachments in the current render pass /must/ not be written in -- any way other than as an attachment by this command -- -- - #VUID-vkCmdDraw-None-09000# If a color attachment is written by any -- prior command in this subpass or by the load, store, or resolve -- operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_COLOR_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDraw-None-09001# If a depth attachment is written by any -- prior command in this subpass or by the load, store, or resolve -- operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDraw-None-09002# If a stencil attachment is written by -- any prior command in this subpass or by the load, store, or resolve -- operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDraw-None-09003# If an attachment is written by any prior -- command in this subpass or by the load, store, or resolve operations -- for this subpass, it /must/ not be accessed in any way other than as -- an attachment, storage image, or sampled image by this command -- -- - #VUID-vkCmdDraw-None-06539# If any previously recorded command in -- the current subpass accessed an image subresource used as an -- attachment in this subpass in any way other than as an attachment, -- this command /must/ not write to that image subresource as an -- attachment -- -- - #VUID-vkCmdDraw-None-06886# If the current render pass instance uses -- a depth\/stencil attachment with a read-only layout for the depth -- aspect, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth-write depth writes> -- /must/ be disabled -- -- - #VUID-vkCmdDraw-None-06887# If the current render pass instance uses -- a depth\/stencil attachment with a read-only layout for the stencil -- aspect, both front and back @writeMask@ are not zero, and stencil -- test is enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil all stencil ops> -- /must/ be 'Vulkan.Core10.Enums.StencilOp.STENCIL_OP_KEEP' -- -- - #VUID-vkCmdDraw-None-07831# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' dynamic -- state enabled then 'cmdSetViewport' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-07832# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' dynamic -- state enabled then 'cmdSetScissor' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-07833# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH' dynamic -- state enabled then 'cmdSetLineWidth' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08617# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', -- 'cmdSetLineWidth' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08618# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08619# If a shader object that outputs line -- primitives is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-07834# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS' dynamic -- state enabled then 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08620# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- in the current command buffer set @depthBiasEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07835# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_BLEND_CONSTANTS' -- dynamic state enabled then 'cmdSetBlendConstants' /must/ have been -- called in the current command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08621# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer set any element of -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', and -- the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- in the current command buffer set the same element of -- @pColorBlendEquations@ to a -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.ColorBlendEquationEXT' -- structure with any 'Vulkan.Core10.Enums.BlendFactor.BlendFactor' -- member with a value of -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_ALPHA', or -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA', -- 'cmdSetBlendConstants' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-07836# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' -- dynamic state enabled, and if the current @depthBoundsTestEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetDepthBounds' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08622# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- in the current command buffer set @depthBoundsTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then 'cmdSetDepthBounds' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07837# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilCompareMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08623# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilCompareMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07838# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilWriteMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08624# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilWriteMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07839# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilReference' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDraw-None-08625# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilReference' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-maxMultiviewInstanceIndex-02688# 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@ -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-02689# 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 -- -- - #VUID-vkCmdDraw-None-06666# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08626# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- in the current command buffer set @sampleLocationsEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-sampleLocationsPerPixel-07934# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDraw-None-07840# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CULL_MODE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08627# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07841# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRONT_FACE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08628# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07843# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08629# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07844# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08630# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07845# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_COMPARE_OP' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08631# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- in the current command buffer set @depthTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07846# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08632# If a shader object is bound to any -- graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBounds depthBounds> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07847# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08633# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07848# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_OP' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08634# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-viewportCount-03417# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - #VUID-vkCmdDraw-scissorCount-03418# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - #VUID-vkCmdDraw-viewportCount-03419# If the bound graphics pipeline -- state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic states enabled then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDraw-None-08635# If a shader object is bound to any -- graphics stage, then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDraw-viewportCount-04137# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-viewportCount-04138# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-None-09232# If a shader object is bound to any -- graphics stage, and the @VK_NV_clip_space_w_scaling@ extension is -- enabled on the device, then -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08636# If a shader object is bound to any -- graphics stage, and the @VK_NV_clip_space_w_scaling@ extension is -- enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-viewportCount-04139# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-viewportCount-04140# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-shadingRateImage-09233# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetCoarseSampleOrderNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-shadingRateImage-09234# If a shader object is bound -- to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- in the current command buffer set shadingRateImageEnable to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08637# If a shader object is bound to any -- graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-VkPipelineVieportCreateInfo-04141# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-VkPipelineVieportCreateInfo-04142# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-None-07878# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07879# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-exclusiveScissor-09235# If a shader object is bound -- to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-exclusiveScissor exclusiveScissor> -- feature is enabled, then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08638# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- in the current command buffer set any element of -- @pExclusiveScissorEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', -- then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-04876# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZER_DISCARD_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08639# If a shader object is bound to any -- graphics stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-04877# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08640# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-logicOp-04878# If the bound graphics pipeline state -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDraw-None-08641# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDraw-primitiveFragmentShadingRateWithMultipleViewports-04552# -- 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' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDraw-primitiveFragmentShadingRateWithMultipleViewports-08642# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, and any shader object bound to a graphics -- stage writes to the @PrimitiveShadingRateKHR@ built-in, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDraw-blendEnable-04727# If rasterization is not disabled -- in the bound graphics pipeline, then for each color attachment in -- the subpass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the @blendEnable@ member of the corresponding element of the -- @pAttachments@ member of @pColorBlendState@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDraw-None-08643# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then for each color -- attachment in the render pass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the corresponding member of @pColorBlendEnables@ in the most -- recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer that affected that attachment index -- /must/ have been 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDraw-multisampledRenderToSingleSampled-07284# If -- rasterization is not disabled in the bound graphics pipeline, and -- none of the @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then @rasterizationSamples@ for the currently -- bound graphics pipeline /must/ be the same as the current subpass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDraw-None-08644# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and none of the -- @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- in the current command buffer /must/ have set @rasterizationSamples@ -- to be the same as the number of samples for the current render pass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDraw-None-08876# If a shader object is bound to any -- graphics stage, the current render pass instance /must/ have been -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdDraw-imageView-06172# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDraw-imageView-06173# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDraw-imageView-06174# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDraw-imageView-06175# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDraw-imageView-06176# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDraw-imageView-06177# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDraw-viewMask-06178# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@viewMask@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@viewMask@ -- -- - #VUID-vkCmdDraw-colorAttachmentCount-06179# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@colorAttachmentCount@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08910# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08911# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, and the current render pass instance was begun -- with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline, or the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@, -- if it exists, /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08912# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound pipeline equal to -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-colorAttachmentCount-09362# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, there is no shader object bound to any graphics stage, -- and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @resolveImageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDraw-None-09363# If there is no shader object bound to -- any graphics stage, the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDraw-None-09364# If the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set the blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDraw-None-09365# If the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDraw-None-09366# If there is a shader object bound to any -- graphics stage, and the current render pass includes a color -- attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDraw-rasterizationSamples-09367# If there is a shader -- object bound to any graphics stage, and the current render pass -- includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDraw-None-09368# If the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDraw-None-09369# If the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDraw-pFragmentSize-09370# If there is a shader object -- bound to any graphics stage, and the current render pass includes a -- color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDraw-pFragmentSize-09371# If there is a shader object -- bound to any graphics stage, and the current render pass includes a -- color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDraw-None-07749# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08646# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-attachmentCount-07750# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then the @attachmentCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ be greater than or equal to the -- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'::@attachmentCount@ -- of the currently bound graphics pipeline -- -- - #VUID-vkCmdDraw-None-08647# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the @attachmentCount@ -- parameter of most recent call to -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- in the current command buffer /must/ be greater than or equal to the -- number of color attachments in the current render pass instance -- -- - #VUID-vkCmdDraw-None-07751# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command for each discard rectangle in -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'::@discardRectangleCount@ -- -- - #VUID-vkCmdDraw-None-07880# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-rasterizerDiscardEnable-09236# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08648# If the @VK_EXT_discard_rectangles@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07881# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08649# If the @VK_EXT_discard_rectangles@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- in the current command buffer set @discardRectangleEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08913# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08914# If current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08915# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08916# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08917# If current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDraw-dynamicRenderingUnusedAttachments-08918# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-imageView-06183# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentShadingRateAttachmentInfoKHR'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdDraw-imageView-06184# If the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentDensityMapAttachmentInfoEXT'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_DENSITY_MAP_ATTACHMENT_BIT_EXT' -- -- - #VUID-vkCmdDraw-colorAttachmentCount-06185# If the currently bound -- pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the corresponding element of the -- @pColorAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDraw-pDepthAttachment-06186# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDraw-pStencilAttachment-06187# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDraw-multisampledRenderToSingleSampled-07285# If the -- currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the value of @rasterizationSamples@ for -- the currently bound graphics pipeline -- -- - #VUID-vkCmdDraw-multisampledRenderToSingleSampled-07286# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDraw-multisampledRenderToSingleSampled-07287# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDraw-pNext-07935# If this command has been called inside -- a render pass instance started with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- and the @pNext@ chain of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo' -- includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT'::@rasterizationSamples@ -- -- - #VUID-vkCmdDraw-renderPass-06198# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline /must/ have been created with a -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@renderPass@ -- equal to 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdDraw-pColorAttachments-08963# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound with a fragment shader that -- statically writes to a color attachment, the color write mask is not -- zero, color writes are enabled, and the corresponding element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-pDepthAttachment-08964# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, depth test is enabled, depth -- write is enabled, and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-pStencilAttachment-08965# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, stencil test is enabled and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDraw-primitivesGeneratedQueryWithRasterizerDiscard-06708# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithRasterizerDiscard primitivesGeneratedQueryWithRasterizerDiscard> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-discard rasterization discard> -- /must/ not be enabled -- -- - #VUID-vkCmdDraw-primitivesGeneratedQueryWithNonZeroStreams-06709# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, the bound graphics pipeline /must/ not have been -- created with a non-zero value in -- 'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@ -- -- - #VUID-vkCmdDraw-None-07619# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07620# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-09237# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08650# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClamp depthClamp> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07621# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08651# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07622# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08652# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07623# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08653# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07624# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-alphaToCoverageEnable-08919# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled, and @alphaToCoverageEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDraw-None-08654# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-alphaToCoverageEnable-08920# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- in the current command buffer set @alphaToCoverageEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDraw-None-07625# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08655# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-alphaToOne alphaToOne> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07626# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08656# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07627# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08657# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07628# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08658# If a shader object is bound to any -- graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- for any attachment set that attachment’s value in -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07629# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08659# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07630# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08660# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryStreams geometryStreams> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07631# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08661# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07632# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08662# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- in the current command buffer set @conservativeRasterizationMode@ to -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_OVERESTIMATE_EXT', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07633# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08663# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipEnable depthClipEnable> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07634# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08664# If the @VK_EXT_sample_locations@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07635# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07636# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08665# If the @VK_EXT_provoking_vertex@ -- extension is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07637# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08666# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08667# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object is bound to the vertex -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08668# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object that outputs line -- primitives is bound to the tessellation evaluation or geometry -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07638# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08669# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08670# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object is bound to the vertex -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08671# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object that outputs line -- primitives is bound to the tessellation evaluation or geometry -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07849# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08672# If the @VK_EXT_line_rasterization@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- in the current command buffer set @stippledLineEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07639# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08673# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipControl depthClipControl> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07640# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08674# If the @VK_NV_clip_space_w_scaling@ -- extension is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07641# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08675# If the @VK_NV_viewport_swizzle@ -- extension is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07642# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08676# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07643# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08677# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- in the current command buffer set @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07644# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08678# If the @VK_NV_framebuffer_mixed_samples@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07645# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08679# If the @VK_NV_framebuffer_mixed_samples@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- in the current command buffer set coverageModulationMode to any -- value other than -- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.COVERAGE_MODULATION_MODE_NONE_NV', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07646# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08680# If the @VK_NV_framebuffer_mixed_samples@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- in the current command buffer set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07647# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-pipelineFragmentShadingRate-09238# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineFragmentShadingRate pipelineFragmentShadingRate> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08681# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07648# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08682# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-representativeFragmentTest representativeFragmentTest> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07649# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08683# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-coverageReductionMode coverageReductionMode> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-pColorBlendEnables-07470# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- set @pColorBlendEnables@ for any attachment to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then for those attachments in -- the subpass the corresponding 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_COLOR_ATTACHMENT_BLEND_BIT' -- -- - #VUID-vkCmdDraw-rasterizationSamples-07471# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and the current subpass does not use any color -- and\/or depth\/stencil attachments, then the @rasterizationSamples@ -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ follow the rules for a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments zero-attachment subpass> -- -- - #VUID-vkCmdDraw-samples-07472# If the bound graphics pipeline state -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@ -- parameter used to create the bound graphics pipeline -- -- - #VUID-vkCmdDraw-samples-07473# If the bound graphics pipeline state -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the @rasterizationSamples@ parameter -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDraw-rasterizationSamples-07474# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and neither the @VK_AMD_mixed_attachment_samples@ nor -- the @VK_NV_framebuffer_mixed_samples@ extensions are enabled, then -- the @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the current subpass color and\/or -- depth\/stencil attachments -- -- - #VUID-vkCmdDraw-None-09211# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, or a shader object is bound to any graphics stage, -- and the current render pass instance includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the @rasterizationSamples@ member of that -- structure -- -- - #VUID-vkCmdDraw-firstAttachment-07476# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- calls /must/ specify an enable for all active color attachments in -- the current subpass -- -- - #VUID-vkCmdDraw-firstAttachment-07477# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- calls /must/ specify the blend equations for all active color -- attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDraw-firstAttachment-07478# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- calls /must/ specify the color write mask for all active color -- attachments in the current subpass -- -- - #VUID-vkCmdDraw-firstAttachment-07479# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- calls /must/ specify the advanced blend equations for all active -- color attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDraw-advancedBlendMaxColorAttachments-07480# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic states enabled and the last calls to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- have enabled advanced blending, then the number of active color -- attachments in the current subpass /must/ not exceed -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendMaxColorAttachments advancedBlendMaxColorAttachments> -- -- - #VUID-vkCmdDraw-primitivesGeneratedQueryWithNonZeroStreams-07481# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, and the bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- state enabled, the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have set the @rasterizationStream@ to zero -- -- - #VUID-vkCmdDraw-sampleLocationsPerPixel-07482# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDraw-sampleLocationsPerPixel-07483# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ parameter of the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07484# If the bound graphics -- pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- 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 -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07485# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.width@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07486# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.height@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07487# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- the fragment shader code /must/ not statically use the extended -- instruction @InterpolateAtSample@ -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07936# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.width@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07937# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.height@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDraw-sampleLocationsEnable-07938# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, @sampleLocationsInfo.sampleLocationsPerPixel@ -- /must/ equal @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDraw-coverageModulationTableEnable-07488# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @coverageModulationTableCount@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ equal the current @rasterizationSamples@ divided by the -- number of color samples in the current subpass -- -- - #VUID-vkCmdDraw-rasterizationSamples-07489# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if -- current subpass has a depth\/stencil attachment and depth test, -- stencil test, or depth bounds test are enabled in the currently -- bound pipeline state, then the current @rasterizationSamples@ /must/ -- be the same as the sample count of the depth\/stencil attachment -- -- - #VUID-vkCmdDraw-coverageToColorEnable-07490# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- set the @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the current subpass -- /must/ have a color attachment at the location selected by the last -- call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- @coverageToColorLocation@, with a -- 'Vulkan.Core10.Enums.Format.Format' of -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_UINT', or -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_SINT' -- -- - #VUID-vkCmdDraw-coverageReductionMode-07491# If this -- @VK_NV_coverage_reduction_mode@ extension is enabled, the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, the current coverage reduction mode -- @coverageReductionMode@, then the current @rasterizationSamples@, -- and the sample counts for the color and depth\/stencil attachments -- (if the subpass has them) /must/ be a valid combination returned by -- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' -- -- - #VUID-vkCmdDraw-viewportCount-07492# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-viewportCount-07493# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDraw-rasterizationSamples-07494# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if the -- current subpass has any color attachments and @rasterizationSamples@ -- of the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- is greater than the number of color samples, then the pipeline -- @sampleShadingEnable@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDraw-stippledLineEnable-07495# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDraw-stippledLineEnable-07496# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_BRESENHAM_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledBresenhamLines stippledBresenhamLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDraw-stippledLineEnable-07497# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledSmoothLines stippledSmoothLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDraw-stippledLineEnable-07498# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_DEFAULT_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@ -- /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE' -- -- - #VUID-vkCmdDraw-conservativePointAndLineRasterization-07499# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-conservativePointAndLineRasterization conservativePointAndLineRasterization> -- is not supported, and the effective primitive topology output by the -- last pre-rasterization shader stage is a line or point, then the -- @conservativeRasterizationMode@ set by the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ be -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_DISABLED_EXT' -- -- - #VUID-vkCmdDraw-stage-07073# If the currently bound pipeline was -- created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT', -- then -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-mesh-shader Mesh Shader Queries> -- /must/ not be active -- -- - #VUID-vkCmdDraw-None-08877# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- dynamic state -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-07850# If dynamic state was inherited from -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV', -- it /must/ be set in the current command buffer prior to this drawing -- command -- -- - #VUID-vkCmdDraw-None-08684# If there is no bound graphics pipeline, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- -- - #VUID-vkCmdDraw-None-08685# If there is no bound graphics pipeline, -- and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT' -- -- - #VUID-vkCmdDraw-None-08686# If there is no bound graphics pipeline, -- and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- -- - #VUID-vkCmdDraw-None-08687# If there is no bound graphics pipeline, -- and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- -- - #VUID-vkCmdDraw-None-08688# If there is no bound graphics pipeline, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- -- - #VUID-vkCmdDraw-None-08689# If there is no bound graphics pipeline, -- and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08690# If there is no bound graphics pipeline, -- and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08693# If there is no bound graphics pipeline, -- and at least one of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features is enabled, one of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages /must/ have a valid 'Vulkan.Extensions.Handles.ShaderEXT' -- bound, and the other /must/ have no -- 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDraw-None-08694# If there is no bound graphics pipeline, -- and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- without the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, a valid 'Vulkan.Extensions.Handles.ShaderEXT' /must/ be bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDraw-None-08695# If there is no bound graphics pipeline, -- and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDraw-None-08696# If there is no bound graphics pipeline, -- and a valid 'Vulkan.Extensions.Handles.ShaderEXT' is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' -- bound to either the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage or the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage -- -- - #VUID-vkCmdDraw-None-08698# If any graphics shader is bound which -- was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, then all shaders created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag in the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ also be bound -- -- - #VUID-vkCmdDraw-None-08699# If any graphics shader is bound which -- was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, any stages in between stages whose shaders which did not -- create a shader with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag as part of the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ not have any 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDraw-None-08878# All bound graphics shader objects /must/ -- have been created with identical or identically defined push -- constant ranges -- -- - #VUID-vkCmdDraw-None-08879# All bound graphics shader objects /must/ -- have been created with identical or identically defined arrays of -- descriptor set layouts -- -- - #VUID-vkCmdDraw-colorAttachmentCount-09372# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- and a fragment shader is bound, it /must/ not declare the -- @DepthReplacing@ or @StencilRefReplacingEXT@ execution modes -- -- - #VUID-vkCmdDraw-None-08880# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopDynamicState attachmentFeedbackLoopDynamicState> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-pDynamicStates-08715# If the bound graphics pipeline -- state includes a fragment shader stage, was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpDepthAttachmentReadEXT@, the @depthWriteEnable@ -- parameter in the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ be 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDraw-pDynamicStates-08716# If the bound graphics pipeline -- state includes a fragment shader stage, was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpStencilAttachmentReadEXT@, the @writeMask@ -- parameter in the last call to 'cmdSetStencilWriteMask' /must/ be @0@ -- -- - #VUID-vkCmdDraw-None-09116# If a shader object is bound to any -- graphics stage or the currently bound graphics pipeline was created -- with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT', -- and the format of any color attachment is -- 'Vulkan.Core10.Enums.Format.FORMAT_E5B9G9R9_UFLOAT_PACK32', the -- corresponding element of the @pColorWriteMasks@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ either include all of -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_R_BIT', -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_G_BIT', -- and -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_B_BIT', -- or none of them -- -- - #VUID-vkCmdDraw-maxFragmentDualSrcAttachments-09239# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blending blending> -- is enabled for any attachment where either the source or destination -- blend factors for that attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-dsb use the secondary color input>, -- the maximum value of @Location@ for any output attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-staticuse statically used> -- in the @Fragment@ @Execution@ @Model@ executed by this command -- /must/ be less than -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxFragmentDualSrcAttachments maxFragmentDualSrcAttachments> -- -- - #VUID-vkCmdDraw-commandBuffer-02712# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, 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 -- -- - #VUID-vkCmdDraw-commandBuffer-02713# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, pipeline stages other than the framebuffer-space -- and compute stages in the 'Vulkan.Core10.Handles.Pipeline' object -- bound to the pipeline bind point used by this command /must/ not -- write to any resource -- -- - #VUID-vkCmdDraw-commandBuffer-04617# If any of the shader stages of -- the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command uses the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirvenv-capabilities-table-RayQueryKHR RayQueryKHR> -- capability, then @commandBuffer@ /must/ not be a protected command -- buffer -- -- - #VUID-vkCmdDraw-None-04007# 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 -- -- - #VUID-vkCmdDraw-None-04008# 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' -- -- - #VUID-vkCmdDraw-None-02721# 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 ???> -- -- - #VUID-vkCmdDraw-None-07842# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-dynamicPrimitiveTopologyUnrestricted-07500# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-dynamicPrimitiveTopologyUnrestricted dynamicPrimitiveTopologyUnrestricted> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- @primitiveTopology@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /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 -- -- - #VUID-vkCmdDraw-None-04912# If the bound graphics pipeline was -- created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic states enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDraw-pStrides-04913# If the bound graphics pipeline was -- created with the -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @pStrides@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ not be @NULL@ -- -- - #VUID-vkCmdDraw-None-08881# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-04914# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDraw-Input-07939# If the bound graphics pipeline state -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then all variables with the @Input@ storage -- class decorated with @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ contain a location in -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@location@ -- -- - #VUID-vkCmdDraw-Input-08734# If the bound graphics pipeline state -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then the numeric type associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be the same as -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- -- - #VUID-vkCmdDraw-format-08936# If there is a shader object bound to a -- graphics stage or the currently bound graphics pipeline was created -- with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then the scalar width associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be 64-bit -- -- - #VUID-vkCmdDraw-format-08937# If there is a shader object bound to a -- graphics stage or the currently bound graphics pipeline was created -- with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and the scalar width associated with a -- @Location@ decorated @Input@ variable in the @Vertex@ @Execution@ -- @Model@ @OpEntryPoint@ is 64-bit, then the corresponding -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- /must/ have a 64-bit component -- -- - #VUID-vkCmdDraw-None-09203# If there is a shader object bound to a -- graphics stage or the currently bound graphics pipeline was created -- with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then all @Input@ variables at the -- corresponding @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ not use components that are not present in the -- format -- -- - #VUID-vkCmdDraw-None-08882# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-04875# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PATCH_CONTROL_POINTS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-08883# If a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-None-04879# If the bound graphics pipeline state was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_RESTART_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-rasterizerDiscardEnable-08884# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDraw-stage-06481# The bound graphics pipeline /must/ not -- have been created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDraw-None-08885# There /must/ be no shader object bound -- to either of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdDraw-commandBuffer-parameter# @commandBuffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDraw-commandBuffer-recording# @commandBuffer@ /must/ be -- in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDraw-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdDraw-renderpass# This command /must/ only be called -- inside of a render pass instance -- -- - #VUID-vkCmdDraw-videocoding# This command /must/ only be called -- outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDraw CommandBuffer commandBuffer "firstViewport" ::: Word32 vertexCount "firstViewport" ::: Word32 instanceCount "firstViewport" ::: Word32 firstVertex "firstViewport" ::: Word32 firstInstance = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDraw is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDraw" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDrawIndexed :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Int32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Int32 -> Word32 -> IO () -- | vkCmdDrawIndexed - Draw primitives with indexed vertices -- -- = 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 -- 'Vulkan.Extensions.VK_KHR_maintenance5.cmdBindIndexBuffer2KHR'::@indexType@ -- or 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' or -- 'Vulkan.Extensions.VK_KHR_maintenance5.cmdBindIndexBuffer2KHR', 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 -- -- - #VUID-vkCmdDrawIndexed-magFilter-04553# 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' -- -- - #VUID-vkCmdDrawIndexed-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_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' -- -- - #VUID-vkCmdDrawIndexed-None-06479# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-02691# 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' -- -- - #VUID-vkCmdDrawIndexed-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-02692# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDrawIndexed-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDrawIndexed-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDrawIndexed-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDrawIndexed-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDrawIndexed-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDrawIndexed-flags-02696# 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' -- -- - #VUID-vkCmdDrawIndexed-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexed-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexed-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexed-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-08600# For each set /n/ that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndexed-None-08601# For each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndexed-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndexed-None-08114# 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 and the bound 'Vulkan.Core10.Handles.Pipeline' -- was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08115# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via 'cmdBindDescriptorSets', the bound -- 'Vulkan.Core10.Handles.Pipeline' /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08116# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08604# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDrawIndexed-None-08117# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08119# If a descriptor is dynamically -- used with a 'Vulkan.Core10.Handles.Pipeline' created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDrawIndexed-None-08605# If a descriptor is dynamically -- used with a 'Vulkan.Extensions.Handles.ShaderEXT' created with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' that was created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDrawIndexed-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDrawIndexed-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDrawIndexed-None-08608# If a pipeline is bound to the -- pipeline bind point used by this command, 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 -- -- - #VUID-vkCmdDrawIndexed-None-08609# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexed-None-08610# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexed-None-08611# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexed-uniformBuffers-06935# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a uniform buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDrawIndexed-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexed-storageBuffers-06936# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a storage buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDrawIndexed-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-02707# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDrawIndexed-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDrawIndexed-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDrawIndexed-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDrawIndexed-format-07753# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDrawIndexed-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' 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 -- -- - #VUID-vkCmdDrawIndexed-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDrawIndexed-OpImageWrite-04469# 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 -- buffer view’s format -- -- - #VUID-vkCmdDrawIndexed-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDrawIndexed-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDrawIndexed-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDrawIndexed-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDrawIndexed-sparseImageInt64Atomics-04474# 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 -- -- - #VUID-vkCmdDrawIndexed-sparseImageInt64Atomics-04475# 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 -- -- - #VUID-vkCmdDrawIndexed-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDrawIndexed-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageWeightedSampleQCOM-06978# If any -- command other than @OpImageWeightedSampleQCOM@, -- @OpImageBoxFilterQCOM@, @OpImageBlockMatchWindowSSDQCOM@, -- @OpImageBlockMatchWindowSADQCOM@, @OpImageBlockMatchGatherSSDQCOM@, -- @OpImageBlockMatchGatherSADQCOM@, @OpImageBlockMatchSSDQCOM@, or -- @OpImageBlockMatchSADQCOM@ uses a 'Vulkan.Core10.Handles.Sampler' as -- a result of this command, then the sampler /must/ not have been -- created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexed-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDrawIndexed-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDrawIndexed-None-07288# Any shader invocation executed by -- this command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDrawIndexed-renderPass-02684# 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' -- -- - #VUID-vkCmdDrawIndexed-subpass-02685# 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' -- -- - #VUID-vkCmdDrawIndexed-None-07748# If any shader statically accesses -- an input attachment, a valid descriptor /must/ be bound to the -- pipeline via a descriptor set -- -- - #VUID-vkCmdDrawIndexed-OpTypeImage-07468# If any shader executed by -- this pipeline accesses an @OpTypeImage@ variable with a @Dim@ -- operand of @SubpassData@, it /must/ be decorated with an -- @InputAttachmentIndex@ that corresponds to a valid input attachment -- in the current subpass -- -- - #VUID-vkCmdDrawIndexed-None-07469# Input attachment views accessed -- in a subpass /must/ be created with the same -- 'Vulkan.Core10.Enums.Format.Format' as the corresponding subpass -- definition, and be created with a 'Vulkan.Core10.Handles.ImageView' -- that is compatible with the attachment referenced by the subpass\' -- @pInputAttachments@[@InputAttachmentIndex@] in the currently bound -- 'Vulkan.Core10.Handles.Framebuffer' as specified by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#compatibility-inputattachment Fragment Input Attachment Compatibility> -- -- - #VUID-vkCmdDrawIndexed-None-06537# Memory backing image subresources -- used as attachments in the current render pass /must/ not be written -- in any way other than as an attachment by this command -- -- - #VUID-vkCmdDrawIndexed-None-09000# If a color attachment is written -- by any prior command in this subpass or by the load, store, or -- resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_COLOR_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndexed-None-09001# If a depth attachment is written -- by any prior command in this subpass or by the load, store, or -- resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndexed-None-09002# If a stencil attachment is -- written by any prior command in this subpass or by the load, store, -- or resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndexed-None-09003# If an attachment is written by -- any prior command in this subpass or by the load, store, or resolve -- operations for this subpass, it /must/ not be accessed in any way -- other than as an attachment, storage image, or sampled image by this -- command -- -- - #VUID-vkCmdDrawIndexed-None-06539# If any previously recorded -- command in the current subpass accessed an image subresource used as -- an attachment in this subpass in any way other than as an -- attachment, this command /must/ not write to that image subresource -- as an attachment -- -- - #VUID-vkCmdDrawIndexed-None-06886# If the current render pass -- instance uses a depth\/stencil attachment with a read-only layout -- for the depth aspect, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth-write depth writes> -- /must/ be disabled -- -- - #VUID-vkCmdDrawIndexed-None-06887# If the current render pass -- instance uses a depth\/stencil attachment with a read-only layout -- for the stencil aspect, both front and back @writeMask@ are not -- zero, and stencil test is enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil all stencil ops> -- /must/ be 'Vulkan.Core10.Enums.StencilOp.STENCIL_OP_KEEP' -- -- - #VUID-vkCmdDrawIndexed-None-07831# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' dynamic -- state enabled then 'cmdSetViewport' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07832# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' dynamic -- state enabled then 'cmdSetScissor' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07833# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH' dynamic -- state enabled then 'cmdSetLineWidth' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08617# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', -- 'cmdSetLineWidth' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08618# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08619# If a shader object that outputs -- line primitives is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07834# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS' dynamic -- state enabled then 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08620# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- in the current command buffer set @depthBiasEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07835# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_BLEND_CONSTANTS' -- dynamic state enabled then 'cmdSetBlendConstants' /must/ have been -- called in the current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08621# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer set any element of -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', and -- the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- in the current command buffer set the same element of -- @pColorBlendEquations@ to a -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.ColorBlendEquationEXT' -- structure with any 'Vulkan.Core10.Enums.BlendFactor.BlendFactor' -- member with a value of -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_ALPHA', or -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA', -- 'cmdSetBlendConstants' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07836# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' -- dynamic state enabled, and if the current @depthBoundsTestEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetDepthBounds' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08622# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- in the current command buffer set @depthBoundsTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then 'cmdSetDepthBounds' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07837# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilCompareMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08623# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilCompareMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07838# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilWriteMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08624# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilWriteMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07839# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilReference' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08625# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilReference' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-maxMultiviewInstanceIndex-02688# 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@ -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-02689# 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 -- -- - #VUID-vkCmdDrawIndexed-None-06666# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08626# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- in the current command buffer set @sampleLocationsEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsPerPixel-07934# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDrawIndexed-None-07840# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CULL_MODE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08627# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07841# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRONT_FACE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08628# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07843# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08629# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07844# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08630# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07845# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_COMPARE_OP' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08631# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- in the current command buffer set @depthTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07846# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08632# If a shader object is bound to -- any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBounds depthBounds> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07847# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08633# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07848# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_OP' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08634# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-viewportCount-03417# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - #VUID-vkCmdDrawIndexed-scissorCount-03418# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - #VUID-vkCmdDrawIndexed-viewportCount-03419# If the bound graphics -- pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic states enabled then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDrawIndexed-None-08635# If a shader object is bound to -- any graphics stage, then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDrawIndexed-viewportCount-04137# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-viewportCount-04138# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-None-09232# If a shader object is bound to -- any graphics stage, and the @VK_NV_clip_space_w_scaling@ extension -- is enabled on the device, then -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08636# If a shader object is bound to -- any graphics stage, and the @VK_NV_clip_space_w_scaling@ extension -- is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-viewportCount-04139# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-viewportCount-04140# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-shadingRateImage-09233# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetCoarseSampleOrderNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-shadingRateImage-09234# If a shader object is -- bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- in the current command buffer set shadingRateImageEnable to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08637# If a shader object is bound to -- any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-VkPipelineVieportCreateInfo-04141# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-VkPipelineVieportCreateInfo-04142# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-None-07878# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07879# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-exclusiveScissor-09235# If a shader object is -- bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-exclusiveScissor exclusiveScissor> -- feature is enabled, then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08638# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- in the current command buffer set any element of -- @pExclusiveScissorEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', -- then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-04876# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZER_DISCARD_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08639# If a shader object is bound to -- any graphics stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-04877# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08640# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-logicOp-04878# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDrawIndexed-None-08641# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDrawIndexed-primitiveFragmentShadingRateWithMultipleViewports-04552# -- 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' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDrawIndexed-primitiveFragmentShadingRateWithMultipleViewports-08642# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, and any shader object bound to a graphics -- stage writes to the @PrimitiveShadingRateKHR@ built-in, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDrawIndexed-blendEnable-04727# If rasterization is not -- disabled in the bound graphics pipeline, then for each color -- attachment in the subpass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the @blendEnable@ member of the corresponding element of the -- @pAttachments@ member of @pColorBlendState@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexed-None-08643# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then for each color -- attachment in the render pass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the corresponding member of @pColorBlendEnables@ in the most -- recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer that affected that attachment index -- /must/ have been 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexed-multisampledRenderToSingleSampled-07284# If -- rasterization is not disabled in the bound graphics pipeline, and -- none of the @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then @rasterizationSamples@ for the currently -- bound graphics pipeline /must/ be the same as the current subpass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndexed-None-08644# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and none of the -- @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- in the current command buffer /must/ have set @rasterizationSamples@ -- to be the same as the number of samples for the current render pass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndexed-None-08876# If a shader object is bound to -- any graphics stage, the current render pass instance /must/ have -- been begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdDrawIndexed-imageView-06172# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndexed-imageView-06173# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndexed-imageView-06174# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndexed-imageView-06175# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndexed-imageView-06176# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndexed-imageView-06177# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndexed-viewMask-06178# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@viewMask@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@viewMask@ -- -- - #VUID-vkCmdDrawIndexed-colorAttachmentCount-06179# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@colorAttachmentCount@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08910# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08911# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, and the current render pass instance was begun -- with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline, or the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@, -- if it exists, /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08912# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound pipeline equal to -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-colorAttachmentCount-09362# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, there is no shader object bound to any graphics stage, -- and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @resolveImageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-None-09363# If there is no shader object -- bound to any graphics stage, the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-None-09364# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set the blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-09365# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-09366# If there is a shader object bound -- to any graphics stage, and the current render pass includes a color -- attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDrawIndexed-rasterizationSamples-09367# If there is a -- shader object bound to any graphics stage, and the current render -- pass includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDrawIndexed-None-09368# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexed-None-09369# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexed-pFragmentSize-09370# If there is a shader -- object bound to any graphics stage, and the current render pass -- includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexed-pFragmentSize-09371# If there is a shader -- object bound to any graphics stage, and the current render pass -- includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexed-None-07749# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08646# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-attachmentCount-07750# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then the @attachmentCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ be greater than or equal to the -- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'::@attachmentCount@ -- of the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-None-08647# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the @attachmentCount@ -- parameter of most recent call to -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- in the current command buffer /must/ be greater than or equal to the -- number of color attachments in the current render pass instance -- -- - #VUID-vkCmdDrawIndexed-None-07751# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command for each discard rectangle in -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'::@discardRectangleCount@ -- -- - #VUID-vkCmdDrawIndexed-None-07880# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-rasterizerDiscardEnable-09236# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08648# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07881# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08649# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- in the current command buffer set @discardRectangleEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08913# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08914# If -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08915# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08916# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08917# If -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexed-dynamicRenderingUnusedAttachments-08918# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-imageView-06183# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentShadingRateAttachmentInfoKHR'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdDrawIndexed-imageView-06184# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentDensityMapAttachmentInfoEXT'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_DENSITY_MAP_ATTACHMENT_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-colorAttachmentCount-06185# If the currently -- bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the corresponding element of the -- @pColorAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-pDepthAttachment-06186# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexed-pStencilAttachment-06187# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexed-multisampledRenderToSingleSampled-07285# If -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the value of @rasterizationSamples@ for -- the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-multisampledRenderToSingleSampled-07286# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexed-multisampledRenderToSingleSampled-07287# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexed-pNext-07935# If this command has been called -- inside a render pass instance started with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- and the @pNext@ chain of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo' -- includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT'::@rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndexed-renderPass-06198# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline /must/ have been created with a -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@renderPass@ -- equal to 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdDrawIndexed-pColorAttachments-08963# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound with a fragment shader that -- statically writes to a color attachment, the color write mask is not -- zero, color writes are enabled, and the corresponding element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-pDepthAttachment-08964# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, depth test is enabled, depth -- write is enabled, and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-pStencilAttachment-08965# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, stencil test is enabled and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexed-primitivesGeneratedQueryWithRasterizerDiscard-06708# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithRasterizerDiscard primitivesGeneratedQueryWithRasterizerDiscard> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-discard rasterization discard> -- /must/ not be enabled -- -- - #VUID-vkCmdDrawIndexed-primitivesGeneratedQueryWithNonZeroStreams-06709# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, the bound graphics pipeline /must/ not have been -- created with a non-zero value in -- 'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@ -- -- - #VUID-vkCmdDrawIndexed-None-07619# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07620# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-09237# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08650# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClamp depthClamp> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07621# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08651# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07622# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08652# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07623# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08653# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07624# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-alphaToCoverageEnable-08919# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled, and @alphaToCoverageEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDrawIndexed-None-08654# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-alphaToCoverageEnable-08920# If a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- in the current command buffer set @alphaToCoverageEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDrawIndexed-None-07625# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08655# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-alphaToOne alphaToOne> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07626# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08656# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07627# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08657# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07628# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08658# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- for any attachment set that attachment’s value in -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07629# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08659# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07630# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08660# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryStreams geometryStreams> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07631# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08661# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07632# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08662# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- in the current command buffer set @conservativeRasterizationMode@ to -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_OVERESTIMATE_EXT', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07633# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08663# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipEnable depthClipEnable> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07634# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08664# If the @VK_EXT_sample_locations@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07635# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07636# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08665# If the @VK_EXT_provoking_vertex@ -- extension is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07637# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08666# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08667# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to the vertex stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08668# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object that outputs line primitives is bound to the tessellation -- evaluation or geometry stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07638# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08669# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08670# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to the vertex stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08671# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object that outputs line primitives is bound to the tessellation -- evaluation or geometry stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07849# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08672# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- in the current command buffer set @stippledLineEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07639# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08673# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipControl depthClipControl> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07640# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08674# If the -- @VK_NV_clip_space_w_scaling@ extension is enabled, and a shader -- object is bound to any graphics stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07641# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08675# If the @VK_NV_viewport_swizzle@ -- extension is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07642# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08676# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07643# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08677# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- in the current command buffer set @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07644# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08678# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07645# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08679# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- in the current command buffer set coverageModulationMode to any -- value other than -- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.COVERAGE_MODULATION_MODE_NONE_NV', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07646# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08680# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- in the current command buffer set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07647# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-pipelineFragmentShadingRate-09238# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineFragmentShadingRate pipelineFragmentShadingRate> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08681# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07648# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08682# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-representativeFragmentTest representativeFragmentTest> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07649# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08683# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-coverageReductionMode coverageReductionMode> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-pColorBlendEnables-07470# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- set @pColorBlendEnables@ for any attachment to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then for those attachments in -- the subpass the corresponding 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_COLOR_ATTACHMENT_BLEND_BIT' -- -- - #VUID-vkCmdDrawIndexed-rasterizationSamples-07471# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and the current subpass does not use any color -- and\/or depth\/stencil attachments, then the @rasterizationSamples@ -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ follow the rules for a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments zero-attachment subpass> -- -- - #VUID-vkCmdDrawIndexed-samples-07472# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@ -- parameter used to create the bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexed-samples-07473# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the @rasterizationSamples@ parameter -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexed-rasterizationSamples-07474# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and neither the @VK_AMD_mixed_attachment_samples@ nor -- the @VK_NV_framebuffer_mixed_samples@ extensions are enabled, then -- the @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the current subpass color and\/or -- depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndexed-None-09211# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, or a shader object is bound to any graphics stage, -- and the current render pass instance includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the @rasterizationSamples@ member of that -- structure -- -- - #VUID-vkCmdDrawIndexed-firstAttachment-07476# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- calls /must/ specify an enable for all active color attachments in -- the current subpass -- -- - #VUID-vkCmdDrawIndexed-firstAttachment-07477# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- calls /must/ specify the blend equations for all active color -- attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDrawIndexed-firstAttachment-07478# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- calls /must/ specify the color write mask for all active color -- attachments in the current subpass -- -- - #VUID-vkCmdDrawIndexed-firstAttachment-07479# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- calls /must/ specify the advanced blend equations for all active -- color attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDrawIndexed-advancedBlendMaxColorAttachments-07480# If -- the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic states enabled and the last calls to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- have enabled advanced blending, then the number of active color -- attachments in the current subpass /must/ not exceed -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendMaxColorAttachments advancedBlendMaxColorAttachments> -- -- - #VUID-vkCmdDrawIndexed-primitivesGeneratedQueryWithNonZeroStreams-07481# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, and the bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- state enabled, the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have set the @rasterizationStream@ to zero -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsPerPixel-07482# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsPerPixel-07483# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ parameter of the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07484# If the bound -- graphics pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- 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 -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07485# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.width@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07486# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.height@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07487# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- the fragment shader code /must/ not statically use the extended -- instruction @InterpolateAtSample@ -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07936# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.width@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07937# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.height@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexed-sampleLocationsEnable-07938# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, @sampleLocationsInfo.sampleLocationsPerPixel@ -- /must/ equal @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexed-coverageModulationTableEnable-07488# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @coverageModulationTableCount@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ equal the current @rasterizationSamples@ divided by the -- number of color samples in the current subpass -- -- - #VUID-vkCmdDrawIndexed-rasterizationSamples-07489# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if -- current subpass has a depth\/stencil attachment and depth test, -- stencil test, or depth bounds test are enabled in the currently -- bound pipeline state, then the current @rasterizationSamples@ /must/ -- be the same as the sample count of the depth\/stencil attachment -- -- - #VUID-vkCmdDrawIndexed-coverageToColorEnable-07490# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- set the @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the current subpass -- /must/ have a color attachment at the location selected by the last -- call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- @coverageToColorLocation@, with a -- 'Vulkan.Core10.Enums.Format.Format' of -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_UINT', or -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_SINT' -- -- - #VUID-vkCmdDrawIndexed-coverageReductionMode-07491# If this -- @VK_NV_coverage_reduction_mode@ extension is enabled, the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, the current coverage reduction mode -- @coverageReductionMode@, then the current @rasterizationSamples@, -- and the sample counts for the color and depth\/stencil attachments -- (if the subpass has them) /must/ be a valid combination returned by -- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' -- -- - #VUID-vkCmdDrawIndexed-viewportCount-07492# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-viewportCount-07493# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexed-rasterizationSamples-07494# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if the -- current subpass has any color attachments and @rasterizationSamples@ -- of the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- is greater than the number of color samples, then the pipeline -- @sampleShadingEnable@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexed-stippledLineEnable-07495# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndexed-stippledLineEnable-07496# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_BRESENHAM_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledBresenhamLines stippledBresenhamLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndexed-stippledLineEnable-07497# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledSmoothLines stippledSmoothLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndexed-stippledLineEnable-07498# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_DEFAULT_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@ -- /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE' -- -- - #VUID-vkCmdDrawIndexed-conservativePointAndLineRasterization-07499# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-conservativePointAndLineRasterization conservativePointAndLineRasterization> -- is not supported, and the effective primitive topology output by the -- last pre-rasterization shader stage is a line or point, then the -- @conservativeRasterizationMode@ set by the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ be -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_DISABLED_EXT' -- -- - #VUID-vkCmdDrawIndexed-stage-07073# If the currently bound pipeline -- was created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT', -- then -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-mesh-shader Mesh Shader Queries> -- /must/ not be active -- -- - #VUID-vkCmdDrawIndexed-None-08877# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- dynamic state -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-07850# If dynamic state was inherited -- from -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV', -- it /must/ be set in the current command buffer prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexed-None-08684# If there is no bound graphics -- pipeline, 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' -- /must/ have been called in the current command buffer with @pStages@ -- with an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-08685# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-08686# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-08687# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-08688# If there is no bound graphics -- pipeline, 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' -- /must/ have been called in the current command buffer with @pStages@ -- with an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- -- - #VUID-vkCmdDrawIndexed-None-08689# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08690# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08693# If there is no bound graphics -- pipeline, and at least one of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features is enabled, one of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages /must/ have a valid 'Vulkan.Extensions.Handles.ShaderEXT' -- bound, and the other /must/ have no -- 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDrawIndexed-None-08694# If there is no bound graphics -- pipeline, and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- without the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, a valid 'Vulkan.Extensions.Handles.ShaderEXT' /must/ be bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndexed-None-08695# If there is no bound graphics -- pipeline, and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndexed-None-08696# If there is no bound graphics -- pipeline, and a valid 'Vulkan.Extensions.Handles.ShaderEXT' is bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' -- bound to either the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage or the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndexed-None-08698# If any graphics shader is bound -- which was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, then all shaders created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag in the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ also be bound -- -- - #VUID-vkCmdDrawIndexed-None-08699# If any graphics shader is bound -- which was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, any stages in between stages whose shaders which did not -- create a shader with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag as part of the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ not have any 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDrawIndexed-None-08878# All bound graphics shader objects -- /must/ have been created with identical or identically defined push -- constant ranges -- -- - #VUID-vkCmdDrawIndexed-None-08879# All bound graphics shader objects -- /must/ have been created with identical or identically defined -- arrays of descriptor set layouts -- -- - #VUID-vkCmdDrawIndexed-colorAttachmentCount-09372# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- and a fragment shader is bound, it /must/ not declare the -- @DepthReplacing@ or @StencilRefReplacingEXT@ execution modes -- -- - #VUID-vkCmdDrawIndexed-None-08880# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopDynamicState attachmentFeedbackLoopDynamicState> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-pDynamicStates-08715# If the bound graphics -- pipeline state includes a fragment shader stage, was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpDepthAttachmentReadEXT@, the @depthWriteEnable@ -- parameter in the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ be 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexed-pDynamicStates-08716# If the bound graphics -- pipeline state includes a fragment shader stage, was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpStencilAttachmentReadEXT@, the @writeMask@ -- parameter in the last call to 'cmdSetStencilWriteMask' /must/ be @0@ -- -- - #VUID-vkCmdDrawIndexed-None-09116# If a shader object is bound to -- any graphics stage or the currently bound graphics pipeline was -- created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT', -- and the format of any color attachment is -- 'Vulkan.Core10.Enums.Format.FORMAT_E5B9G9R9_UFLOAT_PACK32', the -- corresponding element of the @pColorWriteMasks@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ either include all of -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_R_BIT', -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_G_BIT', -- and -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_B_BIT', -- or none of them -- -- - #VUID-vkCmdDrawIndexed-maxFragmentDualSrcAttachments-09239# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blending blending> -- is enabled for any attachment where either the source or destination -- blend factors for that attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-dsb use the secondary color input>, -- the maximum value of @Location@ for any output attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-staticuse statically used> -- in the @Fragment@ @Execution@ @Model@ executed by this command -- /must/ be less than -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxFragmentDualSrcAttachments maxFragmentDualSrcAttachments> -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-02712# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, 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 -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-02713# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, pipeline stages other than the framebuffer-space -- and compute stages in the 'Vulkan.Core10.Handles.Pipeline' object -- bound to the pipeline bind point used by this command /must/ not -- write to any resource -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-04617# If any of the shader -- stages of the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline -- bind point used by this command uses the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirvenv-capabilities-table-RayQueryKHR RayQueryKHR> -- capability, then @commandBuffer@ /must/ not be a protected command -- buffer -- -- - #VUID-vkCmdDrawIndexed-None-04007# 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 -- -- - #VUID-vkCmdDrawIndexed-None-04008# 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' -- -- - #VUID-vkCmdDrawIndexed-None-02721# 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 ???> -- -- - #VUID-vkCmdDrawIndexed-None-07842# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-dynamicPrimitiveTopologyUnrestricted-07500# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-dynamicPrimitiveTopologyUnrestricted dynamicPrimitiveTopologyUnrestricted> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- @primitiveTopology@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /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 -- -- - #VUID-vkCmdDrawIndexed-None-04912# If the bound graphics pipeline -- was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic states enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDrawIndexed-pStrides-04913# If the bound graphics -- pipeline was created with the -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @pStrides@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ not be @NULL@ -- -- - #VUID-vkCmdDrawIndexed-None-08881# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-04914# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDrawIndexed-Input-07939# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then all variables with the @Input@ storage -- class decorated with @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ contain a location in -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@location@ -- -- - #VUID-vkCmdDrawIndexed-Input-08734# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then the numeric type associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be the same as -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- -- - #VUID-vkCmdDrawIndexed-format-08936# If there is a shader object -- bound to a graphics stage or the currently bound graphics pipeline -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then the scalar width associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be 64-bit -- -- - #VUID-vkCmdDrawIndexed-format-08937# If there is a shader object -- bound to a graphics stage or the currently bound graphics pipeline -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and the scalar width associated with a -- @Location@ decorated @Input@ variable in the @Vertex@ @Execution@ -- @Model@ @OpEntryPoint@ is 64-bit, then the corresponding -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- /must/ have a 64-bit component -- -- - #VUID-vkCmdDrawIndexed-None-09203# If there is a shader object bound -- to a graphics stage or the currently bound graphics pipeline was -- created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then all @Input@ variables at the -- corresponding @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ not use components that are not present in the -- format -- -- - #VUID-vkCmdDrawIndexed-None-08882# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-04875# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PATCH_CONTROL_POINTS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-08883# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-None-04879# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_RESTART_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-rasterizerDiscardEnable-08884# If a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexed-stage-06481# The bound graphics pipeline -- /must/ not have been created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexed-None-08885# There /must/ be no shader object -- bound to either of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages -- -- - #VUID-vkCmdDrawIndexed-None-07312# An index buffer /must/ be bound -- -- - #VUID-vkCmdDrawIndexed-robustBufferAccess2-07825# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2> -- is not enabled, (@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' -- -- - #VUID-vkCmdDrawIndexed-robustBufferAccess2-08798# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2> -- is not enabled, (@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' or -- 'Vulkan.Extensions.VK_KHR_maintenance5.cmdBindIndexBuffer2KHR'. If -- 'Vulkan.Extensions.VK_KHR_maintenance5.cmdBindIndexBuffer2KHR' is -- used to bind the index buffer, the size of the bound index buffer is -- 'Vulkan.Extensions.VK_KHR_maintenance5.cmdBindIndexBuffer2KHR'::@size@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDrawIndexed-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdDrawIndexed-renderpass# This command /must/ only be -- called inside of a render pass instance -- -- - #VUID-vkCmdDrawIndexed-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> io () cmdDrawIndexed CommandBuffer commandBuffer "firstViewport" ::: Word32 indexCount "firstViewport" ::: Word32 instanceCount "firstViewport" ::: Word32 firstIndex "vertexOffset" ::: Int32 vertexOffset "firstViewport" ::: Word32 firstInstance = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDrawIndexed is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDrawIndexed" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDrawIndirect :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO () -- | vkCmdDrawIndirect - Draw primitives with indirect parameters -- -- = 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 -- -- - #VUID-vkCmdDrawIndirect-magFilter-04553# 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' -- -- - #VUID-vkCmdDrawIndirect-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_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' -- -- - #VUID-vkCmdDrawIndirect-None-06479# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-02691# 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' -- -- - #VUID-vkCmdDrawIndirect-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-02692# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDrawIndirect-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDrawIndirect-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDrawIndirect-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDrawIndirect-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDrawIndirect-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDrawIndirect-flags-02696# 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' -- -- - #VUID-vkCmdDrawIndirect-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndirect-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndirect-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndirect-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-08600# For each set /n/ that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndirect-None-08601# For each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndirect-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndirect-None-08114# 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 and the bound 'Vulkan.Core10.Handles.Pipeline' -- was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08115# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via 'cmdBindDescriptorSets', the bound -- 'Vulkan.Core10.Handles.Pipeline' /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08116# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08604# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDrawIndirect-None-08117# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08119# If a descriptor is dynamically -- used with a 'Vulkan.Core10.Handles.Pipeline' created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDrawIndirect-None-08605# If a descriptor is dynamically -- used with a 'Vulkan.Extensions.Handles.ShaderEXT' created with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' that was created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDrawIndirect-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDrawIndirect-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDrawIndirect-None-08608# If a pipeline is bound to the -- pipeline bind point used by this command, 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 -- -- - #VUID-vkCmdDrawIndirect-None-08609# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndirect-None-08610# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndirect-None-08611# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndirect-uniformBuffers-06935# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a uniform buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDrawIndirect-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndirect-storageBuffers-06936# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a storage buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDrawIndirect-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndirect-commandBuffer-02707# If @commandBuffer@ is -- an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDrawIndirect-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDrawIndirect-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDrawIndirect-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDrawIndirect-format-07753# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDrawIndirect-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' 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 -- -- - #VUID-vkCmdDrawIndirect-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDrawIndirect-OpImageWrite-04469# 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 -- buffer view’s format -- -- - #VUID-vkCmdDrawIndirect-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDrawIndirect-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDrawIndirect-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDrawIndirect-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDrawIndirect-sparseImageInt64Atomics-04474# 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 -- -- - #VUID-vkCmdDrawIndirect-sparseImageInt64Atomics-04475# 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 -- -- - #VUID-vkCmdDrawIndirect-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDrawIndirect-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageWeightedSampleQCOM-06978# If any -- command other than @OpImageWeightedSampleQCOM@, -- @OpImageBoxFilterQCOM@, @OpImageBlockMatchWindowSSDQCOM@, -- @OpImageBlockMatchWindowSADQCOM@, @OpImageBlockMatchGatherSSDQCOM@, -- @OpImageBlockMatchGatherSADQCOM@, @OpImageBlockMatchSSDQCOM@, or -- @OpImageBlockMatchSADQCOM@ uses a 'Vulkan.Core10.Handles.Sampler' as -- a result of this command, then the sampler /must/ not have been -- created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndirect-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDrawIndirect-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDrawIndirect-None-07288# Any shader invocation executed -- by this command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDrawIndirect-renderPass-02684# 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' -- -- - #VUID-vkCmdDrawIndirect-subpass-02685# 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' -- -- - #VUID-vkCmdDrawIndirect-None-07748# If any shader statically -- accesses an input attachment, a valid descriptor /must/ be bound to -- the pipeline via a descriptor set -- -- - #VUID-vkCmdDrawIndirect-OpTypeImage-07468# If any shader executed by -- this pipeline accesses an @OpTypeImage@ variable with a @Dim@ -- operand of @SubpassData@, it /must/ be decorated with an -- @InputAttachmentIndex@ that corresponds to a valid input attachment -- in the current subpass -- -- - #VUID-vkCmdDrawIndirect-None-07469# Input attachment views accessed -- in a subpass /must/ be created with the same -- 'Vulkan.Core10.Enums.Format.Format' as the corresponding subpass -- definition, and be created with a 'Vulkan.Core10.Handles.ImageView' -- that is compatible with the attachment referenced by the subpass\' -- @pInputAttachments@[@InputAttachmentIndex@] in the currently bound -- 'Vulkan.Core10.Handles.Framebuffer' as specified by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#compatibility-inputattachment Fragment Input Attachment Compatibility> -- -- - #VUID-vkCmdDrawIndirect-None-06537# Memory backing image -- subresources used as attachments in the current render pass /must/ -- not be written in any way other than as an attachment by this -- command -- -- - #VUID-vkCmdDrawIndirect-None-09000# If a color attachment is written -- by any prior command in this subpass or by the load, store, or -- resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_COLOR_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndirect-None-09001# If a depth attachment is written -- by any prior command in this subpass or by the load, store, or -- resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndirect-None-09002# If a stencil attachment is -- written by any prior command in this subpass or by the load, store, -- or resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndirect-None-09003# If an attachment is written by -- any prior command in this subpass or by the load, store, or resolve -- operations for this subpass, it /must/ not be accessed in any way -- other than as an attachment, storage image, or sampled image by this -- command -- -- - #VUID-vkCmdDrawIndirect-None-06539# If any previously recorded -- command in the current subpass accessed an image subresource used as -- an attachment in this subpass in any way other than as an -- attachment, this command /must/ not write to that image subresource -- as an attachment -- -- - #VUID-vkCmdDrawIndirect-None-06886# If the current render pass -- instance uses a depth\/stencil attachment with a read-only layout -- for the depth aspect, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth-write depth writes> -- /must/ be disabled -- -- - #VUID-vkCmdDrawIndirect-None-06887# If the current render pass -- instance uses a depth\/stencil attachment with a read-only layout -- for the stencil aspect, both front and back @writeMask@ are not -- zero, and stencil test is enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil all stencil ops> -- /must/ be 'Vulkan.Core10.Enums.StencilOp.STENCIL_OP_KEEP' -- -- - #VUID-vkCmdDrawIndirect-None-07831# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' dynamic -- state enabled then 'cmdSetViewport' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07832# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' dynamic -- state enabled then 'cmdSetScissor' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07833# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH' dynamic -- state enabled then 'cmdSetLineWidth' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08617# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', -- 'cmdSetLineWidth' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08618# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08619# If a shader object that outputs -- line primitives is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07834# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS' dynamic -- state enabled then 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08620# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- in the current command buffer set @depthBiasEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07835# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_BLEND_CONSTANTS' -- dynamic state enabled then 'cmdSetBlendConstants' /must/ have been -- called in the current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08621# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer set any element of -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', and -- the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- in the current command buffer set the same element of -- @pColorBlendEquations@ to a -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.ColorBlendEquationEXT' -- structure with any 'Vulkan.Core10.Enums.BlendFactor.BlendFactor' -- member with a value of -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_ALPHA', or -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA', -- 'cmdSetBlendConstants' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07836# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' -- dynamic state enabled, and if the current @depthBoundsTestEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetDepthBounds' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08622# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- in the current command buffer set @depthBoundsTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then 'cmdSetDepthBounds' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07837# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilCompareMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08623# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilCompareMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07838# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilWriteMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08624# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilWriteMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07839# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilReference' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08625# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilReference' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-maxMultiviewInstanceIndex-02688# 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@ -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-02689# 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 -- -- - #VUID-vkCmdDrawIndirect-None-06666# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08626# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- in the current command buffer set @sampleLocationsEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsPerPixel-07934# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDrawIndirect-None-07840# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CULL_MODE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08627# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07841# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRONT_FACE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08628# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07843# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08629# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07844# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08630# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07845# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_COMPARE_OP' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08631# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- in the current command buffer set @depthTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07846# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08632# If a shader object is bound to -- any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBounds depthBounds> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07847# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08633# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07848# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_OP' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08634# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-viewportCount-03417# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - #VUID-vkCmdDrawIndirect-scissorCount-03418# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - #VUID-vkCmdDrawIndirect-viewportCount-03419# If the bound graphics -- pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic states enabled then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDrawIndirect-None-08635# If a shader object is bound to -- any graphics stage, then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDrawIndirect-viewportCount-04137# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-viewportCount-04138# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-None-09232# If a shader object is bound to -- any graphics stage, and the @VK_NV_clip_space_w_scaling@ extension -- is enabled on the device, then -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08636# If a shader object is bound to -- any graphics stage, and the @VK_NV_clip_space_w_scaling@ extension -- is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-viewportCount-04139# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-viewportCount-04140# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-shadingRateImage-09233# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetCoarseSampleOrderNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-shadingRateImage-09234# If a shader object -- is bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- in the current command buffer set shadingRateImageEnable to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08637# If a shader object is bound to -- any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-VkPipelineVieportCreateInfo-04141# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-VkPipelineVieportCreateInfo-04142# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-None-07878# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07879# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-exclusiveScissor-09235# If a shader object -- is bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-exclusiveScissor exclusiveScissor> -- feature is enabled, then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08638# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- in the current command buffer set any element of -- @pExclusiveScissorEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', -- then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-04876# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZER_DISCARD_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08639# If a shader object is bound to -- any graphics stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-04877# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08640# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-logicOp-04878# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDrawIndirect-None-08641# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDrawIndirect-primitiveFragmentShadingRateWithMultipleViewports-04552# -- 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' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDrawIndirect-primitiveFragmentShadingRateWithMultipleViewports-08642# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, and any shader object bound to a graphics -- stage writes to the @PrimitiveShadingRateKHR@ built-in, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDrawIndirect-blendEnable-04727# If rasterization is not -- disabled in the bound graphics pipeline, then for each color -- attachment in the subpass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the @blendEnable@ member of the corresponding element of the -- @pAttachments@ member of @pColorBlendState@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndirect-None-08643# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then for each color -- attachment in the render pass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the corresponding member of @pColorBlendEnables@ in the most -- recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer that affected that attachment index -- /must/ have been 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndirect-multisampledRenderToSingleSampled-07284# If -- rasterization is not disabled in the bound graphics pipeline, and -- none of the @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then @rasterizationSamples@ for the currently -- bound graphics pipeline /must/ be the same as the current subpass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndirect-None-08644# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and none of the -- @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- in the current command buffer /must/ have set @rasterizationSamples@ -- to be the same as the number of samples for the current render pass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndirect-None-08876# If a shader object is bound to -- any graphics stage, the current render pass instance /must/ have -- been begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdDrawIndirect-imageView-06172# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndirect-imageView-06173# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndirect-imageView-06174# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndirect-imageView-06175# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndirect-imageView-06176# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndirect-imageView-06177# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndirect-viewMask-06178# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@viewMask@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@viewMask@ -- -- - #VUID-vkCmdDrawIndirect-colorAttachmentCount-06179# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@colorAttachmentCount@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08910# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08911# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, and the current render pass instance was begun -- with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline, or the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@, -- if it exists, /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08912# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound pipeline equal to -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-colorAttachmentCount-09362# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, there is no shader object bound to any graphics stage, -- and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @resolveImageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-None-09363# If there is no shader object -- bound to any graphics stage, the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-None-09364# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set the blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-09365# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-09366# If there is a shader object -- bound to any graphics stage, and the current render pass includes a -- color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDrawIndirect-rasterizationSamples-09367# If there is a -- shader object bound to any graphics stage, and the current render -- pass includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDrawIndirect-None-09368# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndirect-None-09369# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndirect-pFragmentSize-09370# If there is a shader -- object bound to any graphics stage, and the current render pass -- includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndirect-pFragmentSize-09371# If there is a shader -- object bound to any graphics stage, and the current render pass -- includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndirect-None-07749# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08646# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-attachmentCount-07750# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then the @attachmentCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ be greater than or equal to the -- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'::@attachmentCount@ -- of the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-None-08647# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the @attachmentCount@ -- parameter of most recent call to -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- in the current command buffer /must/ be greater than or equal to the -- number of color attachments in the current render pass instance -- -- - #VUID-vkCmdDrawIndirect-None-07751# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command for each discard rectangle in -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'::@discardRectangleCount@ -- -- - #VUID-vkCmdDrawIndirect-None-07880# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-rasterizerDiscardEnable-09236# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08648# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07881# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08649# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- in the current command buffer set @discardRectangleEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08913# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08914# If -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08915# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08916# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08917# If -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndirect-dynamicRenderingUnusedAttachments-08918# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-imageView-06183# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentShadingRateAttachmentInfoKHR'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdDrawIndirect-imageView-06184# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentDensityMapAttachmentInfoEXT'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_DENSITY_MAP_ATTACHMENT_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-colorAttachmentCount-06185# If the currently -- bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the corresponding element of the -- @pColorAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-pDepthAttachment-06186# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndirect-pStencilAttachment-06187# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndirect-multisampledRenderToSingleSampled-07285# If -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the value of @rasterizationSamples@ for -- the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-multisampledRenderToSingleSampled-07286# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndirect-multisampledRenderToSingleSampled-07287# If -- the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndirect-pNext-07935# If this command has been called -- inside a render pass instance started with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- and the @pNext@ chain of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo' -- includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT'::@rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndirect-renderPass-06198# If the current render pass -- instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline /must/ have been created with a -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@renderPass@ -- equal to 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdDrawIndirect-pColorAttachments-08963# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound with a fragment shader that -- statically writes to a color attachment, the color write mask is not -- zero, color writes are enabled, and the corresponding element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-pDepthAttachment-08964# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, depth test is enabled, depth -- write is enabled, and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-pStencilAttachment-08965# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, stencil test is enabled and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndirect-primitivesGeneratedQueryWithRasterizerDiscard-06708# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithRasterizerDiscard primitivesGeneratedQueryWithRasterizerDiscard> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-discard rasterization discard> -- /must/ not be enabled -- -- - #VUID-vkCmdDrawIndirect-primitivesGeneratedQueryWithNonZeroStreams-06709# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, the bound graphics pipeline /must/ not have been -- created with a non-zero value in -- 'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@ -- -- - #VUID-vkCmdDrawIndirect-None-07619# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07620# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-09237# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08650# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClamp depthClamp> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07621# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08651# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07622# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08652# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07623# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08653# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07624# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-alphaToCoverageEnable-08919# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled, and @alphaToCoverageEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDrawIndirect-None-08654# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-alphaToCoverageEnable-08920# If a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- in the current command buffer set @alphaToCoverageEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDrawIndirect-None-07625# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08655# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-alphaToOne alphaToOne> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07626# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08656# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07627# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08657# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07628# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08658# If a shader object is bound to -- any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- for any attachment set that attachment’s value in -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07629# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08659# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07630# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08660# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryStreams geometryStreams> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07631# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08661# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07632# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08662# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- in the current command buffer set @conservativeRasterizationMode@ to -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_OVERESTIMATE_EXT', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07633# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08663# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipEnable depthClipEnable> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07634# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08664# If the @VK_EXT_sample_locations@ -- extension is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07635# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07636# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08665# If the @VK_EXT_provoking_vertex@ -- extension is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07637# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08666# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08667# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to the vertex stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08668# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object that outputs line primitives is bound to the tessellation -- evaluation or geometry stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07638# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08669# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08670# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to the vertex stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08671# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object that outputs line primitives is bound to the tessellation -- evaluation or geometry stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07849# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08672# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- in the current command buffer set @stippledLineEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07639# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08673# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipControl depthClipControl> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07640# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08674# If the -- @VK_NV_clip_space_w_scaling@ extension is enabled, and a shader -- object is bound to any graphics stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07641# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08675# If the @VK_NV_viewport_swizzle@ -- extension is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07642# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08676# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07643# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08677# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- in the current command buffer set @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07644# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08678# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07645# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08679# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- in the current command buffer set coverageModulationMode to any -- value other than -- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.COVERAGE_MODULATION_MODE_NONE_NV', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07646# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08680# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- in the current command buffer set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07647# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-pipelineFragmentShadingRate-09238# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineFragmentShadingRate pipelineFragmentShadingRate> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08681# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07648# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08682# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-representativeFragmentTest representativeFragmentTest> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07649# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08683# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-coverageReductionMode coverageReductionMode> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-pColorBlendEnables-07470# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- set @pColorBlendEnables@ for any attachment to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then for those attachments in -- the subpass the corresponding 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_COLOR_ATTACHMENT_BLEND_BIT' -- -- - #VUID-vkCmdDrawIndirect-rasterizationSamples-07471# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and the current subpass does not use any color -- and\/or depth\/stencil attachments, then the @rasterizationSamples@ -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ follow the rules for a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments zero-attachment subpass> -- -- - #VUID-vkCmdDrawIndirect-samples-07472# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@ -- parameter used to create the bound graphics pipeline -- -- - #VUID-vkCmdDrawIndirect-samples-07473# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the @rasterizationSamples@ parameter -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndirect-rasterizationSamples-07474# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and neither the @VK_AMD_mixed_attachment_samples@ nor -- the @VK_NV_framebuffer_mixed_samples@ extensions are enabled, then -- the @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the current subpass color and\/or -- depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndirect-None-09211# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, or a shader object is bound to any graphics stage, -- and the current render pass instance includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the @rasterizationSamples@ member of that -- structure -- -- - #VUID-vkCmdDrawIndirect-firstAttachment-07476# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- calls /must/ specify an enable for all active color attachments in -- the current subpass -- -- - #VUID-vkCmdDrawIndirect-firstAttachment-07477# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- calls /must/ specify the blend equations for all active color -- attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDrawIndirect-firstAttachment-07478# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- calls /must/ specify the color write mask for all active color -- attachments in the current subpass -- -- - #VUID-vkCmdDrawIndirect-firstAttachment-07479# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- calls /must/ specify the advanced blend equations for all active -- color attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDrawIndirect-advancedBlendMaxColorAttachments-07480# If -- the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic states enabled and the last calls to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- have enabled advanced blending, then the number of active color -- attachments in the current subpass /must/ not exceed -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendMaxColorAttachments advancedBlendMaxColorAttachments> -- -- - #VUID-vkCmdDrawIndirect-primitivesGeneratedQueryWithNonZeroStreams-07481# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, and the bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- state enabled, the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have set the @rasterizationStream@ to zero -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsPerPixel-07482# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsPerPixel-07483# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ parameter of the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07484# If the bound -- graphics pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- 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 -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07485# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.width@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07486# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.height@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07487# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- the fragment shader code /must/ not statically use the extended -- instruction @InterpolateAtSample@ -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07936# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.width@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07937# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.height@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndirect-sampleLocationsEnable-07938# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, @sampleLocationsInfo.sampleLocationsPerPixel@ -- /must/ equal @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndirect-coverageModulationTableEnable-07488# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @coverageModulationTableCount@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ equal the current @rasterizationSamples@ divided by the -- number of color samples in the current subpass -- -- - #VUID-vkCmdDrawIndirect-rasterizationSamples-07489# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if -- current subpass has a depth\/stencil attachment and depth test, -- stencil test, or depth bounds test are enabled in the currently -- bound pipeline state, then the current @rasterizationSamples@ /must/ -- be the same as the sample count of the depth\/stencil attachment -- -- - #VUID-vkCmdDrawIndirect-coverageToColorEnable-07490# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- set the @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the current subpass -- /must/ have a color attachment at the location selected by the last -- call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- @coverageToColorLocation@, with a -- 'Vulkan.Core10.Enums.Format.Format' of -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_UINT', or -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_SINT' -- -- - #VUID-vkCmdDrawIndirect-coverageReductionMode-07491# If this -- @VK_NV_coverage_reduction_mode@ extension is enabled, the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, the current coverage reduction mode -- @coverageReductionMode@, then the current @rasterizationSamples@, -- and the sample counts for the color and depth\/stencil attachments -- (if the subpass has them) /must/ be a valid combination returned by -- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' -- -- - #VUID-vkCmdDrawIndirect-viewportCount-07492# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-viewportCount-07493# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndirect-rasterizationSamples-07494# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if the -- current subpass has any color attachments and @rasterizationSamples@ -- of the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- is greater than the number of color samples, then the pipeline -- @sampleShadingEnable@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndirect-stippledLineEnable-07495# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndirect-stippledLineEnable-07496# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_BRESENHAM_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledBresenhamLines stippledBresenhamLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndirect-stippledLineEnable-07497# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledSmoothLines stippledSmoothLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndirect-stippledLineEnable-07498# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_DEFAULT_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@ -- /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE' -- -- - #VUID-vkCmdDrawIndirect-conservativePointAndLineRasterization-07499# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-conservativePointAndLineRasterization conservativePointAndLineRasterization> -- is not supported, and the effective primitive topology output by the -- last pre-rasterization shader stage is a line or point, then the -- @conservativeRasterizationMode@ set by the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ be -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_DISABLED_EXT' -- -- - #VUID-vkCmdDrawIndirect-stage-07073# If the currently bound pipeline -- was created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT', -- then -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-mesh-shader Mesh Shader Queries> -- /must/ not be active -- -- - #VUID-vkCmdDrawIndirect-None-08877# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- dynamic state -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-07850# If dynamic state was inherited -- from -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV', -- it /must/ be set in the current command buffer prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndirect-None-08684# If there is no bound graphics -- pipeline, 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' -- /must/ have been called in the current command buffer with @pStages@ -- with an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-08685# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-08686# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-08687# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-08688# If there is no bound graphics -- pipeline, 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' -- /must/ have been called in the current command buffer with @pStages@ -- with an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- -- - #VUID-vkCmdDrawIndirect-None-08689# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08690# If there is no bound graphics -- pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08693# If there is no bound graphics -- pipeline, and at least one of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features is enabled, one of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages /must/ have a valid 'Vulkan.Extensions.Handles.ShaderEXT' -- bound, and the other /must/ have no -- 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDrawIndirect-None-08694# If there is no bound graphics -- pipeline, and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- without the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, a valid 'Vulkan.Extensions.Handles.ShaderEXT' /must/ be bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndirect-None-08695# If there is no bound graphics -- pipeline, and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndirect-None-08696# If there is no bound graphics -- pipeline, and a valid 'Vulkan.Extensions.Handles.ShaderEXT' is bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' -- bound to either the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage or the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndirect-None-08698# If any graphics shader is bound -- which was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, then all shaders created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag in the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ also be bound -- -- - #VUID-vkCmdDrawIndirect-None-08699# If any graphics shader is bound -- which was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, any stages in between stages whose shaders which did not -- create a shader with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag as part of the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ not have any 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDrawIndirect-None-08878# All bound graphics shader -- objects /must/ have been created with identical or identically -- defined push constant ranges -- -- - #VUID-vkCmdDrawIndirect-None-08879# All bound graphics shader -- objects /must/ have been created with identical or identically -- defined arrays of descriptor set layouts -- -- - #VUID-vkCmdDrawIndirect-colorAttachmentCount-09372# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- and a fragment shader is bound, it /must/ not declare the -- @DepthReplacing@ or @StencilRefReplacingEXT@ execution modes -- -- - #VUID-vkCmdDrawIndirect-None-08880# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopDynamicState attachmentFeedbackLoopDynamicState> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-pDynamicStates-08715# If the bound graphics -- pipeline state includes a fragment shader stage, was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpDepthAttachmentReadEXT@, the @depthWriteEnable@ -- parameter in the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ be 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndirect-pDynamicStates-08716# If the bound graphics -- pipeline state includes a fragment shader stage, was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpStencilAttachmentReadEXT@, the @writeMask@ -- parameter in the last call to 'cmdSetStencilWriteMask' /must/ be @0@ -- -- - #VUID-vkCmdDrawIndirect-None-09116# If a shader object is bound to -- any graphics stage or the currently bound graphics pipeline was -- created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT', -- and the format of any color attachment is -- 'Vulkan.Core10.Enums.Format.FORMAT_E5B9G9R9_UFLOAT_PACK32', the -- corresponding element of the @pColorWriteMasks@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ either include all of -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_R_BIT', -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_G_BIT', -- and -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_B_BIT', -- or none of them -- -- - #VUID-vkCmdDrawIndirect-maxFragmentDualSrcAttachments-09239# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blending blending> -- is enabled for any attachment where either the source or destination -- blend factors for that attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-dsb use the secondary color input>, -- the maximum value of @Location@ for any output attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-staticuse statically used> -- in the @Fragment@ @Execution@ @Model@ executed by this command -- /must/ be less than -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxFragmentDualSrcAttachments maxFragmentDualSrcAttachments> -- -- - #VUID-vkCmdDrawIndirect-None-04007# 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 -- -- - #VUID-vkCmdDrawIndirect-None-04008# 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' -- -- - #VUID-vkCmdDrawIndirect-None-02721# 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 ???> -- -- - #VUID-vkCmdDrawIndirect-None-07842# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-dynamicPrimitiveTopologyUnrestricted-07500# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-dynamicPrimitiveTopologyUnrestricted dynamicPrimitiveTopologyUnrestricted> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- @primitiveTopology@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /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 -- -- - #VUID-vkCmdDrawIndirect-None-04912# If the bound graphics pipeline -- was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic states enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDrawIndirect-pStrides-04913# If the bound graphics -- pipeline was created with the -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @pStrides@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ not be @NULL@ -- -- - #VUID-vkCmdDrawIndirect-None-08881# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-04914# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDrawIndirect-Input-07939# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then all variables with the @Input@ storage -- class decorated with @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ contain a location in -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@location@ -- -- - #VUID-vkCmdDrawIndirect-Input-08734# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then the numeric type associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be the same as -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- -- - #VUID-vkCmdDrawIndirect-format-08936# If there is a shader object -- bound to a graphics stage or the currently bound graphics pipeline -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then the scalar width associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be 64-bit -- -- - #VUID-vkCmdDrawIndirect-format-08937# If there is a shader object -- bound to a graphics stage or the currently bound graphics pipeline -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and the scalar width associated with a -- @Location@ decorated @Input@ variable in the @Vertex@ @Execution@ -- @Model@ @OpEntryPoint@ is 64-bit, then the corresponding -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- /must/ have a 64-bit component -- -- - #VUID-vkCmdDrawIndirect-None-09203# If there is a shader object -- bound to a graphics stage or the currently bound graphics pipeline -- was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then all @Input@ variables at the -- corresponding @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ not use components that are not present in the -- format -- -- - #VUID-vkCmdDrawIndirect-None-08882# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-04875# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PATCH_CONTROL_POINTS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-08883# If a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-None-04879# If the bound graphics pipeline -- state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_RESTART_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-rasterizerDiscardEnable-08884# If a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndirect-stage-06481# The bound graphics pipeline -- /must/ not have been created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDrawIndirect-None-08885# There /must/ be no shader object -- bound to either of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages -- -- - #VUID-vkCmdDrawIndirect-buffer-02708# If @buffer@ is non-sparse then -- it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdDrawIndirect-buffer-02709# @buffer@ /must/ have been -- created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT' -- bit set -- -- - #VUID-vkCmdDrawIndirect-offset-02710# @offset@ /must/ be a multiple -- of @4@ -- -- - #VUID-vkCmdDrawIndirect-commandBuffer-02711# @commandBuffer@ /must/ -- not be a protected command buffer -- -- - #VUID-vkCmdDrawIndirect-drawCount-02718# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multiDrawIndirect> -- feature is not enabled, @drawCount@ /must/ be @0@ or @1@ -- -- - #VUID-vkCmdDrawIndirect-drawCount-02719# @drawCount@ /must/ be less -- than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDrawIndirectCount@ -- -- - #VUID-vkCmdDrawIndirect-drawCount-00476# 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') -- -- - #VUID-vkCmdDrawIndirect-drawCount-00487# If @drawCount@ is equal to -- @1@, (@offset@ + -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand')) /must/ be -- less than or equal to the size of @buffer@ -- -- - #VUID-vkCmdDrawIndirect-drawCount-00488# 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) -- -- - #VUID-vkCmdDrawIndirect-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDrawIndirect-buffer-parameter# @buffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdDrawIndirect-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDrawIndirect-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdDrawIndirect-renderpass# This command /must/ only be -- called inside of a render pass instance -- -- - #VUID-vkCmdDrawIndirect-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdDrawIndirect-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDrawIndirect CommandBuffer commandBuffer Buffer buffer "offset" ::: DeviceSize offset "firstViewport" ::: Word32 drawCount "firstViewport" ::: Word32 stride = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndirectPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDrawIndirect is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDrawIndirect" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDrawIndexedIndirect :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO () -- | vkCmdDrawIndexedIndirect - Draw primitives with indirect parameters and -- indexed vertices -- -- = 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-magFilter-04553# 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' -- -- - #VUID-vkCmdDrawIndexedIndirect-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_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' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06479# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-02691# 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' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-02692# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDrawIndexedIndirect-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDrawIndexedIndirect-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDrawIndexedIndirect-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-flags-02696# 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' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08600# For each set /n/ that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08601# For each push constant -- that is statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndexedIndirect-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08114# 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 and the bound 'Vulkan.Core10.Handles.Pipeline' -- was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08115# If the descriptors used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point were specified via 'cmdBindDescriptorSets', the bound -- 'Vulkan.Core10.Handles.Pipeline' /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08116# Descriptors in bound -- descriptor buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08604# Descriptors in bound -- descriptor buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08117# If the descriptors used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08119# If a descriptor is -- dynamically used with a 'Vulkan.Core10.Handles.Pipeline' created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08605# If a descriptor is -- dynamically used with a 'Vulkan.Extensions.Handles.ShaderEXT' -- created with a 'Vulkan.Core10.Handles.DescriptorSetLayout' that was -- created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08608# If a pipeline is bound to -- the pipeline bind point used by this command, 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08609# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08610# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08611# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-uniformBuffers-06935# If any stage of -- the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a uniform buffer, and that -- stage was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-storageBuffers-06936# If any stage of -- the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a storage buffer, and that -- stage was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-commandBuffer-02707# If -- @commandBuffer@ is an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDrawIndexedIndirect-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDrawIndexedIndirect-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDrawIndexedIndirect-format-07753# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWrite-04469# 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 -- buffer view’s format -- -- - #VUID-vkCmdDrawIndexedIndirect-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDrawIndexedIndirect-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDrawIndexedIndirect-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-sparseImageInt64Atomics-04474# 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-sparseImageInt64Atomics-04475# 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageWeightedSampleQCOM-06978# If -- any command other than @OpImageWeightedSampleQCOM@, -- @OpImageBoxFilterQCOM@, @OpImageBlockMatchWindowSSDQCOM@, -- @OpImageBlockMatchWindowSADQCOM@, @OpImageBlockMatchGatherSSDQCOM@, -- @OpImageBlockMatchGatherSADQCOM@, @OpImageBlockMatchSSDQCOM@, or -- @OpImageBlockMatchSADQCOM@ uses a 'Vulkan.Core10.Handles.Sampler' as -- a result of this command, then the sampler /must/ not have been -- created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDrawIndexedIndirect-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07288# Any shader invocation -- executed by this command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDrawIndexedIndirect-renderPass-02684# 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' -- -- - #VUID-vkCmdDrawIndexedIndirect-subpass-02685# 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' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07748# If any shader statically -- accesses an input attachment, a valid descriptor /must/ be bound to -- the pipeline via a descriptor set -- -- - #VUID-vkCmdDrawIndexedIndirect-OpTypeImage-07468# If any shader -- executed by this pipeline accesses an @OpTypeImage@ variable with a -- @Dim@ operand of @SubpassData@, it /must/ be decorated with an -- @InputAttachmentIndex@ that corresponds to a valid input attachment -- in the current subpass -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07469# Input attachment views -- accessed in a subpass /must/ be created with the same -- 'Vulkan.Core10.Enums.Format.Format' as the corresponding subpass -- definition, and be created with a 'Vulkan.Core10.Handles.ImageView' -- that is compatible with the attachment referenced by the subpass\' -- @pInputAttachments@[@InputAttachmentIndex@] in the currently bound -- 'Vulkan.Core10.Handles.Framebuffer' as specified by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#compatibility-inputattachment Fragment Input Attachment Compatibility> -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06537# Memory backing image -- subresources used as attachments in the current render pass /must/ -- not be written in any way other than as an attachment by this -- command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09000# If a color attachment is -- written by any prior command in this subpass or by the load, store, -- or resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_COLOR_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09001# If a depth attachment is -- written by any prior command in this subpass or by the load, store, -- or resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09002# If a stencil attachment -- is written by any prior command in this subpass or by the load, -- store, or resolve operations for this subpass, it is not in the -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- image layout, and either: -- -- - the -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DEPTH_STENCIL_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- is set on the currently bound pipeline or -- -- - the last call to -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- included -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' -- and -- -- - there is no currently bound graphics pipeline or -- -- - the currently bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- it /must/ not be accessed in any way other than as an -- attachment by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09003# If an attachment is -- written by any prior command in this subpass or by the load, store, -- or resolve operations for this subpass, it /must/ not be accessed in -- any way other than as an attachment, storage image, or sampled image -- by this command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06539# If any previously -- recorded command in the current subpass accessed an image -- subresource used as an attachment in this subpass in any way other -- than as an attachment, this command /must/ not write to that image -- subresource as an attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06886# If the current render -- pass instance uses a depth\/stencil attachment with a read-only -- layout for the depth aspect, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth-write depth writes> -- /must/ be disabled -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06887# If the current render -- pass instance uses a depth\/stencil attachment with a read-only -- layout for the stencil aspect, both front and back @writeMask@ are -- not zero, and stencil test is enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil all stencil ops> -- /must/ be 'Vulkan.Core10.Enums.StencilOp.STENCIL_OP_KEEP' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07831# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' dynamic -- state enabled then 'cmdSetViewport' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07832# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' dynamic -- state enabled then 'cmdSetScissor' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07833# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH' dynamic -- state enabled then 'cmdSetLineWidth' /must/ have been called in the -- current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08617# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', -- 'cmdSetLineWidth' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08618# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08619# If a shader object that -- outputs line primitives is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, 'cmdSetLineWidth' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07834# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS' dynamic -- state enabled then 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08620# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- in the current command buffer set @depthBiasEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetDepthBias' or -- 'Vulkan.Extensions.VK_EXT_depth_bias_control.cmdSetDepthBias2EXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07835# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_BLEND_CONSTANTS' -- dynamic state enabled then 'cmdSetBlendConstants' /must/ have been -- called in the current command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08621# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer set any element of -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', and -- the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- in the current command buffer set the same element of -- @pColorBlendEquations@ to a -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.ColorBlendEquationEXT' -- structure with any 'Vulkan.Core10.Enums.BlendFactor.BlendFactor' -- member with a value of -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_COLOR', -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_ALPHA', or -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA', -- 'cmdSetBlendConstants' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07836# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' -- dynamic state enabled, and if the current @depthBoundsTestEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetDepthBounds' /must/ have been called in the current command -- buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08622# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- in the current command buffer set @depthBoundsTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then 'cmdSetDepthBounds' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07837# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilCompareMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08623# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilCompareMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07838# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilWriteMask' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08624# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilWriteMask' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07839# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' -- dynamic state enabled, and if the current @stencilTestEnable@ state -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'cmdSetStencilReference' /must/ have been called in the current -- command buffer prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08625# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', 'cmdSetStencilReference' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-maxMultiviewInstanceIndex-02688# 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@ -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-02689# 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-06666# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08626# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- in the current command buffer set @sampleLocationsEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsPerPixel-07934# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07840# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CULL_MODE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08627# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetCullMode' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07841# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRONT_FACE' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08628# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetFrontFace' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07843# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08629# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07844# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08630# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07845# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_COMPARE_OP' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08631# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthTestEnable' -- in the current command buffer set @depthTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthCompareOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07846# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08632# If a shader object is -- bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBounds depthBounds> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07847# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_TEST_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08633# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07848# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_OP' dynamic -- state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08634# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilTestEnable' -- in the current command buffer set @stencilTestEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetStencilOp' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-03417# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-scissorCount-03418# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-03419# If the bound -- graphics pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic states enabled then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08635# If a shader object is -- bound to any graphics stage, then both -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- and -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetScissorWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-04137# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-04138# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09232# If a shader object is -- bound to any graphics stage, and the @VK_NV_clip_space_w_scaling@ -- extension is enabled on the device, then -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08636# If a shader object is -- bound to any graphics stage, and the @VK_NV_clip_space_w_scaling@ -- extension is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-04139# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-04140# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-shadingRateImage-09233# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetCoarseSampleOrderNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-shadingRateImage-09234# If a shader -- object is bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- in the current command buffer set shadingRateImageEnable to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08637# If a shader object is -- bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled on the device, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-VkPipelineVieportCreateInfo-04141# If -- the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-VkPipelineVieportCreateInfo-04142# If -- the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled and a -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- structure chained from -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo', 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07878# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07879# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-exclusiveScissor-09235# If a shader -- object is bound to any graphics stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-exclusiveScissor exclusiveScissor> -- feature is enabled, then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08638# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorEnableNV' -- in the current command buffer set any element of -- @pExclusiveScissorEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', -- then -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04876# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZER_DISCARD_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08639# If a shader object is -- bound to any graphics stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04877# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08640# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetDepthBiasEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-logicOp-04878# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08641# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetLogicOpEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command and the @logicOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.LogicOp.LogicOp' value -- -- - #VUID-vkCmdDrawIndexedIndirect-primitiveFragmentShadingRateWithMultipleViewports-04552# -- 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' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDrawIndexedIndirect-primitiveFragmentShadingRateWithMultipleViewports-08642# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, and any shader object bound to a graphics -- stage writes to the @PrimitiveShadingRateKHR@ built-in, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the @viewportCount@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- /must/ be @1@ -- -- - #VUID-vkCmdDrawIndexedIndirect-blendEnable-04727# If rasterization -- is not disabled in the bound graphics pipeline, then for each color -- attachment in the subpass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the @blendEnable@ member of the corresponding element of the -- @pAttachments@ member of @pColorBlendState@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08643# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then for each color -- attachment in the render pass, if the corresponding image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- do not contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT', -- then the corresponding member of @pColorBlendEnables@ in the most -- recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- in the current command buffer that affected that attachment index -- /must/ have been 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexedIndirect-multisampledRenderToSingleSampled-07284# -- If rasterization is not disabled in the bound graphics pipeline, and -- none of the @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then @rasterizationSamples@ for the currently -- bound graphics pipeline /must/ be the same as the current subpass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08644# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and none of the -- @VK_AMD_mixed_attachment_samples@ extension, the -- @VK_NV_framebuffer_mixed_samples@ extension, or the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is enabled, then the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- in the current command buffer /must/ have set @rasterizationSamples@ -- to be the same as the number of samples for the current render pass -- color and\/or depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08876# If a shader object is -- bound to any graphics stage, the current render pass instance /must/ -- have been begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06172# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06173# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06174# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06175# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06176# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pDepthAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pDepthAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the depth attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06177# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @imageView@ member of @pStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the @layout@ member of -- @pStencilAttachment@ is -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- this command /must/ not write any values to the stencil attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-viewMask-06178# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@viewMask@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@viewMask@ -- -- - #VUID-vkCmdDrawIndexedIndirect-colorAttachmentCount-06179# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound graphics pipeline /must/ have been created with -- a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@colorAttachmentCount@ -- equal to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08910# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08911# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, and the current render pass instance was begun -- with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a 'Vulkan.Core10.Enums.Format.Format' equal to the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound graphics pipeline, or the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@, -- if it exists, /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08912# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the currently bound pipeline equal to -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-colorAttachmentCount-09362# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, there is no shader object bound to any graphics stage, -- and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @resolveImageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09363# If there is no shader -- object bound to any graphics stage, the current render pass instance -- was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, and a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with an image created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value equal to the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09364# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set the blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09365# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09366# If there is a shader -- object bound to any graphics stage, and the current render pass -- includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have set blend enable to -- 'Vulkan.Core10.FundamentalTypes.FALSE' prior to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizationSamples-09367# If there -- is a shader object bound to any graphics stage, and the current -- render pass includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have set @rasterizationSamples@ to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' prior -- to this drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09368# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09369# If the current render -- pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is no shader object bound to any graphics stage, and the -- currently bound graphics pipeline was created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value and with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexedIndirect-pFragmentSize-09370# If there is a -- shader object bound to any graphics stage, and the current render -- pass includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->width@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexedIndirect-pFragmentSize-09371# If there is a -- shader object bound to any graphics stage, and the current render -- pass includes a color attachment that uses the -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID' -- resolve mode, then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- /must/ have set @pFragmentSize->height@ to @1@ prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07749# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08646# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-attachmentCount-07750# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT' -- dynamic state enabled then the @attachmentCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- /must/ be greater than or equal to the -- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'::@attachmentCount@ -- of the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08647# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable> -- feature is enabled on the device, and a shader object is bound to -- the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the @attachmentCount@ -- parameter of most recent call to -- 'Vulkan.Extensions.VK_EXT_color_write_enable.cmdSetColorWriteEnableEXT' -- in the current command buffer /must/ be greater than or equal to the -- number of color attachments in the current render pass instance -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07751# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command for each discard rectangle in -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'::@discardRectangleCount@ -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07880# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizerDiscardEnable-09236# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08648# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07881# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08649# If the -- @VK_EXT_discard_rectangles@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEnableEXT' -- in the current command buffer set @discardRectangleEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08913# -- If the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08914# -- If current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08915# -- If the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08916# -- If the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08917# -- If current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline /must/ be equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicRenderingUnusedAttachments-08918# -- If the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dynamicRenderingUnusedAttachments dynamicRenderingUnusedAttachments> -- feature is enabled, -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the currently bound graphics pipeline was not equal -- to the 'Vulkan.Core10.Enums.Format.Format' used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@, -- the value of the format /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06183# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentShadingRateAttachmentInfoKHR'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdDrawIndexedIndirect-imageView-06184# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.RenderingFragmentDensityMapAttachmentInfoEXT'::@imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the currently -- bound graphics pipeline /must/ have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RENDERING_FRAGMENT_DENSITY_MAP_ATTACHMENT_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-colorAttachmentCount-06185# If the -- currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the corresponding element of the -- @pColorAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-pDepthAttachment-06186# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexedIndirect-pStencilAttachment-06187# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created with a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- used to create the currently bound graphics pipeline /must/ be equal -- to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexedIndirect-multisampledRenderToSingleSampled-07285# -- If the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and the current render pass instance was -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter greater than @0@, then each element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- array with a @imageView@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /must/ have been created -- with a sample count equal to the value of @rasterizationSamples@ for -- the currently bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-multisampledRenderToSingleSampled-07286# -- If the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexedIndirect-multisampledRenderToSingleSampled-07287# -- If the current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline was created without a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multisampledRenderToSingleSampled multisampledRenderToSingleSampled> -- feature is not enabled, and -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to the sample count used to create -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- -- - #VUID-vkCmdDrawIndexedIndirect-pNext-07935# If this command has been -- called inside a render pass instance started with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- and the @pNext@ chain of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo' -- includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the value of -- @rasterizationSamples@ for the currently bound graphics pipeline -- /must/ be equal to -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT'::@rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndexedIndirect-renderPass-06198# If the current -- render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the currently bound pipeline /must/ have been created with a -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@renderPass@ -- equal to 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdDrawIndexedIndirect-pColorAttachments-08963# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound with a fragment shader that -- statically writes to a color attachment, the color write mask is not -- zero, color writes are enabled, and the corresponding element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- corresponding element of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@pColorAttachmentFormats@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-pDepthAttachment-08964# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, depth test is enabled, depth -- write is enabled, and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@depthAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-pStencilAttachment-08965# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- there is a graphics pipeline bound, stencil test is enabled and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.PipelineRenderingCreateInfo'::@stencilAttachmentFormat@ -- used to create the pipeline /must/ not be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdDrawIndexedIndirect-primitivesGeneratedQueryWithRasterizerDiscard-06708# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithRasterizerDiscard primitivesGeneratedQueryWithRasterizerDiscard> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-discard rasterization discard> -- /must/ not be enabled -- -- - #VUID-vkCmdDrawIndexedIndirect-primitivesGeneratedQueryWithNonZeroStreams-06709# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, the bound graphics pipeline /must/ not have been -- created with a non-zero value in -- 'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@ -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07619# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07620# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09237# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetTessellationDomainOriginEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08650# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClamp depthClamp> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClampEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07621# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08651# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07622# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08652# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07623# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08653# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07624# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-alphaToCoverageEnable-08919# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT' -- dynamic state enabled, and @alphaToCoverageEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08654# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-alphaToCoverageEnable-08920# If a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToCoverageEnableEXT' -- in the current command buffer set @alphaToCoverageEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface> -- /must/ contain a variable for the alpha @Component@ word in -- @Location@ 0 at @Index@ 0 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07625# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08655# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-alphaToOne alphaToOne> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetAlphaToOneEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07626# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08656# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logicOp> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLogicOpEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07627# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08657# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07628# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08658# If a shader object is -- bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- for any attachment set that attachment’s value in -- @pColorBlendEnables@ to 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07629# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08659# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07630# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08660# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryStreams geometryStreams> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07631# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08661# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07632# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08662# If the -- @VK_EXT_conservative_rasterization@ extension is enabled, and a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- in the current command buffer set @conservativeRasterizationMode@ to -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_OVERESTIMATE_EXT', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetExtraPrimitiveOverestimationSizeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07633# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08663# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipEnable depthClipEnable> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07634# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08664# If the -- @VK_EXT_sample_locations@ extension is enabled, and a shader object -- is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07635# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07636# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08665# If the -- @VK_EXT_provoking_vertex@ extension is enabled, and a shader object -- is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetProvokingVertexModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07637# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08666# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08667# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to the vertex stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08668# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object that outputs line primitives is bound to the tessellation -- evaluation or geometry stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineRasterizationModeEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07638# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08669# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetPolygonModeEXT' -- in the current command buffer set @polygonMode@ to -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08670# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to the vertex stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- in the current command buffer set @primitiveTopology@ to any line -- topology, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08671# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object that outputs line primitives is bound to the tessellation -- evaluation or geometry stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07849# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08672# If the -- @VK_EXT_line_rasterization@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetLineStippleEnableEXT' -- in the current command buffer set @stippledLineEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07639# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08673# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClipControl depthClipControl> -- feature is enabled, and a shader object is bound to any graphics -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetDepthClipNegativeOneToOneEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07640# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08674# If the -- @VK_NV_clip_space_w_scaling@ extension is enabled, and a shader -- object is bound to any graphics stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportWScalingEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07641# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08675# If the -- @VK_NV_viewport_swizzle@ extension is enabled, and a shader object -- is bound to any graphics stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07642# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08676# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07643# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08677# If the -- @VK_NV_fragment_coverage_to_color@ extension is enabled, and a -- shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- in the current command buffer set @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07644# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08678# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07645# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08679# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationModeNV' -- in the current command buffer set coverageModulationMode to any -- value other than -- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.COVERAGE_MODULATION_MODE_NONE_NV', -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07646# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08680# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and a shader -- object is bound to any graphics stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', and the most recent call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- in the current command buffer set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07647# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-pipelineFragmentShadingRate-09238# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineFragmentShadingRate pipelineFragmentShadingRate> -- feature is enabled, and a shader object is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set rasterizerDiscardEnable to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR' -- must have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08681# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetShadingRateImageEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07648# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08682# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-representativeFragmentTest representativeFragmentTest> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRepresentativeFragmentTestEnableNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07649# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08683# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-coverageReductionMode coverageReductionMode> -- feature is enabled, and a shader object is bound to any graphics -- stage, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageReductionModeNV' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-pColorBlendEnables-07470# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- set @pColorBlendEnables@ for any attachment to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then for those attachments in -- the subpass the corresponding 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_COLOR_ATTACHMENT_BLEND_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizationSamples-07471# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and the current subpass does not use any color -- and\/or depth\/stencil attachments, then the @rasterizationSamples@ -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ follow the rules for a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments zero-attachment subpass> -- -- - #VUID-vkCmdDrawIndexedIndirect-samples-07472# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@ -- parameter used to create the bound graphics pipeline -- -- - #VUID-vkCmdDrawIndexedIndirect-samples-07473# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' -- state and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, then the @samples@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleMaskEXT' -- /must/ be greater or equal to the @rasterizationSamples@ parameter -- in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizationSamples-07474# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, and neither the @VK_AMD_mixed_attachment_samples@ nor -- the @VK_NV_framebuffer_mixed_samples@ extensions are enabled, then -- the @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the current subpass color and\/or -- depth\/stencil attachments -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09211# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, or a shader object is bound to any graphics stage, -- and the current render pass instance includes a -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure with @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- /must/ be the same as the @rasterizationSamples@ member of that -- structure -- -- - #VUID-vkCmdDrawIndexedIndirect-firstAttachment-07476# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- calls /must/ specify an enable for all active color attachments in -- the current subpass -- -- - #VUID-vkCmdDrawIndexedIndirect-firstAttachment-07477# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEquationEXT' -- calls /must/ specify the blend equations for all active color -- attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDrawIndexedIndirect-firstAttachment-07478# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- calls /must/ specify the color write mask for all active color -- attachments in the current subpass -- -- - #VUID-vkCmdDrawIndexedIndirect-firstAttachment-07479# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command, and the attachments specified by the -- @firstAttachment@ and @attachmentCount@ parameters of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- calls /must/ specify the advanced blend equations for all active -- color attachments in the current subpass where blending is enabled -- -- - #VUID-vkCmdDrawIndexedIndirect-advancedBlendMaxColorAttachments-07480# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT' -- dynamic states enabled and the last calls to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendEnableEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorBlendAdvancedEXT' -- have enabled advanced blending, then the number of active color -- attachments in the current subpass /must/ not exceed -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendMaxColorAttachments advancedBlendMaxColorAttachments> -- -- - #VUID-vkCmdDrawIndexedIndirect-primitivesGeneratedQueryWithNonZeroStreams-07481# -- If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-primitivesGeneratedQueryWithNonZeroStreams primitivesGeneratedQueryWithNonZeroStreams> -- feature is not enabled and the -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- query is active, and the bound graphics pipeline was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT' -- state enabled, the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationStreamEXT' -- /must/ have set the @rasterizationStream@ to zero -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsPerPixel-07482# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state disabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ member of the -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' -- structure the bound graphics pipeline has been created with -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsPerPixel-07483# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, then the @sampleLocationsPerPixel@ member of -- @pSampleLocationsInfo@ in the last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ equal the @rasterizationSamples@ parameter of the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07484# If the -- bound graphics pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07485# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.width@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07486# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state enabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- then the @sampleLocationsInfo.sampleLocationGridSize.height@ in the -- last call to -- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT' -- /must/ evenly divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling @rasterizationSamples@ -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07487# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, and if @sampleLocationsEnable@ was -- 'Vulkan.Core10.FundamentalTypes.TRUE' in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetSampleLocationsEnableEXT', -- the fragment shader code /must/ not statically use the extended -- instruction @InterpolateAtSample@ -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07936# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.width@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07937# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, -- @sampleLocationsInfo.sampleLocationGridSize.height@ /must/ evenly -- divide -- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@ -- as returned by -- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT' -- with a @samples@ parameter equaling the value of -- @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-sampleLocationsEnable-07938# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- state disabled and the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- state enabled, the @sampleLocationsEnable@ member of a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- in the bound graphics pipeline is -- 'Vulkan.Core10.FundamentalTypes.TRUE' or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT' -- state enabled, then, @sampleLocationsInfo.sampleLocationsPerPixel@ -- /must/ equal @rasterizationSamples@ in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-coverageModulationTableEnable-07488# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableEnableNV' -- set @coverageModulationTableEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the -- @coverageModulationTableCount@ parameter in the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageModulationTableNV' -- /must/ equal the current @rasterizationSamples@ divided by the -- number of color samples in the current subpass -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizationSamples-07489# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if -- current subpass has a depth\/stencil attachment and depth test, -- stencil test, or depth bounds test are enabled in the currently -- bound pipeline state, then the current @rasterizationSamples@ /must/ -- be the same as the sample count of the depth\/stencil attachment -- -- - #VUID-vkCmdDrawIndexedIndirect-coverageToColorEnable-07490# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- state enabled and the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorEnableNV' -- set the @coverageToColorEnable@ to -- 'Vulkan.Core10.FundamentalTypes.TRUE', then the current subpass -- /must/ have a color attachment at the location selected by the last -- call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetCoverageToColorLocationNV' -- @coverageToColorLocation@, with a -- 'Vulkan.Core10.Enums.Format.Format' of -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R8_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_UINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R16_SINT', -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_UINT', or -- 'Vulkan.Core10.Enums.Format.FORMAT_R32_SINT' -- -- - #VUID-vkCmdDrawIndexedIndirect-coverageReductionMode-07491# If this -- @VK_NV_coverage_reduction_mode@ extension is enabled, the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT' -- states enabled, the current coverage reduction mode -- @coverageReductionMode@, then the current @rasterizationSamples@, -- and the sample counts for the color and depth\/stencil attachments -- (if the subpass has them) /must/ be a valid combination returned by -- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-07492# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic state enabled, 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.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-viewportCount-07493# If the bound -- graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetViewportSwizzleNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetViewportWithCount' -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizationSamples-07494# If the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, and if the -- current subpass has any color attachments and @rasterizationSamples@ -- of the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetRasterizationSamplesEXT' -- is greater than the number of color samples, then the pipeline -- @sampleShadingEnable@ /must/ be -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexedIndirect-stippledLineEnable-07495# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndexedIndirect-stippledLineEnable-07496# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_BRESENHAM_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledBresenhamLines stippledBresenhamLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndexedIndirect-stippledLineEnable-07497# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledSmoothLines stippledSmoothLines> -- feature /must/ be enabled -- -- - #VUID-vkCmdDrawIndexedIndirect-stippledLineEnable-07498# If the -- bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT' -- or -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT' -- dynamic states enabled, and if the current @stippledLineEnable@ -- state is 'Vulkan.Core10.FundamentalTypes.TRUE' and the current -- @lineRasterizationMode@ state is -- 'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_DEFAULT_EXT', -- then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines> -- feature /must/ be enabled and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@ -- /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE' -- -- - #VUID-vkCmdDrawIndexedIndirect-conservativePointAndLineRasterization-07499# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT' -- dynamic state enabled, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-conservativePointAndLineRasterization conservativePointAndLineRasterization> -- is not supported, and the effective primitive topology output by the -- last pre-rasterization shader stage is a line or point, then the -- @conservativeRasterizationMode@ set by the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetConservativeRasterizationModeEXT' -- /must/ be -- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.CONSERVATIVE_RASTERIZATION_MODE_DISABLED_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-stage-07073# If the currently bound -- pipeline was created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT', -- then -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-mesh-shader Mesh Shader Queries> -- /must/ not be active -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08877# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ATTACHMENT_FEEDBACK_LOOP_ENABLE_EXT' -- dynamic state -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07850# If dynamic state was -- inherited from -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV', -- it /must/ be set in the current command buffer prior to this drawing -- command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08684# If there is no bound -- graphics pipeline, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08685# If there is no bound -- graphics pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08686# If there is no bound -- graphics pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08687# If there is no bound -- graphics pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08688# If there is no bound -- graphics pipeline, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08689# If there is no bound -- graphics pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08690# If there is no bound -- graphics pipeline, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is enabled, -- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT' /must/ -- have been called in the current command buffer with @pStages@ with -- an element of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08693# If there is no bound -- graphics pipeline, and at least one of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features is enabled, one of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages /must/ have a valid 'Vulkan.Extensions.Handles.ShaderEXT' -- bound, and the other /must/ have no -- 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08694# If there is no bound -- graphics pipeline, and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- without the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, a valid 'Vulkan.Extensions.Handles.ShaderEXT' /must/ be bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08695# If there is no bound -- graphics pipeline, and both the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- features are enabled, and a valid -- 'Vulkan.Extensions.Handles.ShaderEXT' is bound the to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage, and that 'Vulkan.Extensions.Handles.ShaderEXT' was created -- with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_NO_TASK_SHADER_BIT_EXT' -- flag, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' bound -- to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08696# If there is no bound -- graphics pipeline, and a valid 'Vulkan.Extensions.Handles.ShaderEXT' -- is bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, there /must/ be no 'Vulkan.Extensions.Handles.ShaderEXT' -- bound to either the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- stage or the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stage -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08698# If any graphics shader is -- bound which was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, then all shaders created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag in the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ also be bound -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08699# If any graphics shader is -- bound which was created with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag, any stages in between stages whose shaders which did not -- create a shader with the -- 'Vulkan.Extensions.VK_EXT_shader_object.SHADER_CREATE_LINK_STAGE_BIT_EXT' -- flag as part of the same -- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT' call -- /must/ not have any 'Vulkan.Extensions.Handles.ShaderEXT' bound -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08878# All bound graphics shader -- objects /must/ have been created with identical or identically -- defined push constant ranges -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08879# All bound graphics shader -- objects /must/ have been created with identical or identically -- defined arrays of descriptor set layouts -- -- - #VUID-vkCmdDrawIndexedIndirect-colorAttachmentCount-09372# If the -- current render pass instance was begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and a -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- equal to @1@, a color attachment with a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- and a fragment shader is bound, it /must/ not declare the -- @DepthReplacing@ or @StencilRefReplacingEXT@ execution modes -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08880# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT' -- stage and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopDynamicState attachmentFeedbackLoopDynamicState> -- feature is enabled on the device, and the most recent call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE' -- 'Vulkan.Extensions.VK_EXT_attachment_feedback_loop_dynamic_state.cmdSetAttachmentFeedbackLoopEnableEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-pDynamicStates-08715# If the bound -- graphics pipeline state includes a fragment shader stage, was -- created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpDepthAttachmentReadEXT@, the @depthWriteEnable@ -- parameter in the last call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnable' -- /must/ be 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - #VUID-vkCmdDrawIndexedIndirect-pDynamicStates-08716# If the bound -- graphics pipeline state includes a fragment shader stage, was -- created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@, -- and the fragment shader declares the @EarlyFragmentTests@ execution -- mode and uses @OpStencilAttachmentReadEXT@, the @writeMask@ -- parameter in the last call to 'cmdSetStencilWriteMask' /must/ be @0@ -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09116# If a shader object is -- bound to any graphics stage or the currently bound graphics pipeline -- was created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT', -- and the format of any color attachment is -- 'Vulkan.Core10.Enums.Format.FORMAT_E5B9G9R9_UFLOAT_PACK32', the -- corresponding element of the @pColorWriteMasks@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state3.cmdSetColorWriteMaskEXT' -- /must/ either include all of -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_R_BIT', -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_G_BIT', -- and -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.COLOR_COMPONENT_B_BIT', -- or none of them -- -- - #VUID-vkCmdDrawIndexedIndirect-maxFragmentDualSrcAttachments-09239# -- If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blending blending> -- is enabled for any attachment where either the source or destination -- blend factors for that attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-dsb use the secondary color input>, -- the maximum value of @Location@ for any output attachment -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-staticuse statically used> -- in the @Fragment@ @Execution@ @Model@ executed by this command -- /must/ be less than -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxFragmentDualSrcAttachments maxFragmentDualSrcAttachments> -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04007# 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 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04008# 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' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-02721# 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 ???> -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07842# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-dynamicPrimitiveTopologyUnrestricted-07500# -- If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' -- dynamic state enabled and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-dynamicPrimitiveTopologyUnrestricted dynamicPrimitiveTopologyUnrestricted> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', then the -- @primitiveTopology@ parameter of -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /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 -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04912# If the bound graphics -- pipeline was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic states enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDrawIndexedIndirect-pStrides-04913# If the bound graphics -- pipeline was created with the -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @pStrides@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT' -- /must/ not be @NULL@ -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08881# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04914# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- draw command -- -- - #VUID-vkCmdDrawIndexedIndirect-Input-07939# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then all variables with the @Input@ storage -- class decorated with @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ contain a location in -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@location@ -- -- - #VUID-vkCmdDrawIndexedIndirect-Input-08734# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, then the numeric type associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be the same as -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- -- - #VUID-vkCmdDrawIndexedIndirect-format-08936# If there is a shader -- object bound to a graphics stage or the currently bound graphics -- pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then the scalar width associated with all -- @Input@ variables of the corresponding @Location@ in the @Vertex@ -- @Execution@ @Model@ @OpEntryPoint@ /must/ be 64-bit -- -- - #VUID-vkCmdDrawIndexedIndirect-format-08937# If there is a shader -- object bound to a graphics stage or the currently bound graphics -- pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and the scalar width associated with a -- @Location@ decorated @Input@ variable in the @Vertex@ @Execution@ -- @Model@ @OpEntryPoint@ is 64-bit, then the corresponding -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- /must/ have a 64-bit component -- -- - #VUID-vkCmdDrawIndexedIndirect-None-09203# If there is a shader -- object bound to a graphics stage or the currently bound graphics -- pipeline was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled, and -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.VertexInputAttributeDescription2EXT'::@format@ -- has a 64-bit component, then all @Input@ variables at the -- corresponding @Location@ in the @Vertex@ @Execution@ @Model@ -- @OpEntryPoint@ /must/ not use components that are not present in the -- format -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08882# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04875# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PATCH_CONTROL_POINTS_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08883# If a shader object is -- bound to the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT' -- stage, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state2.cmdSetPatchControlPointsEXT' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-None-04879# If the bound graphics -- pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_RESTART_ENABLE' -- dynamic state enabled then -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-rasterizerDiscardEnable-08884# If a -- shader object is bound to any graphics stage, and the most recent -- call to -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetRasterizerDiscardEnable' -- in the current command buffer set @rasterizerDiscardEnable@ to -- 'Vulkan.Core10.FundamentalTypes.FALSE', -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2.cmdSetPrimitiveRestartEnable' -- /must/ have been called in the current command buffer prior to this -- drawing command -- -- - #VUID-vkCmdDrawIndexedIndirect-stage-06481# The bound graphics -- pipeline /must/ not have been created with the -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo'::@stage@ -- member of an element of -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'::@pStages@ set -- to -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- -- - #VUID-vkCmdDrawIndexedIndirect-None-08885# There /must/ be no shader -- object bound to either of the -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_EXT' -- stages -- -- - #VUID-vkCmdDrawIndexedIndirect-buffer-02708# If @buffer@ is -- non-sparse then it /must/ be bound completely and contiguously to a -- single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdDrawIndexedIndirect-buffer-02709# @buffer@ /must/ have -- been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT' -- bit set -- -- - #VUID-vkCmdDrawIndexedIndirect-offset-02710# @offset@ /must/ be a -- multiple of @4@ -- -- - #VUID-vkCmdDrawIndexedIndirect-commandBuffer-02711# @commandBuffer@ -- /must/ not be a protected command buffer -- -- - #VUID-vkCmdDrawIndexedIndirect-drawCount-02718# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multiDrawIndirect> -- feature is not enabled, @drawCount@ /must/ be @0@ or @1@ -- -- - #VUID-vkCmdDrawIndexedIndirect-drawCount-02719# @drawCount@ /must/ -- be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDrawIndirectCount@ -- -- - #VUID-vkCmdDrawIndexedIndirect-None-07312# An index buffer /must/ be -- bound -- -- - #VUID-vkCmdDrawIndexedIndirect-robustBufferAccess2-07825# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2> -- is not enabled, (@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' -- -- - #VUID-vkCmdDrawIndexedIndirect-drawCount-00528# 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') -- -- - #VUID-vkCmdDrawIndexedIndirect-drawCount-00539# If @drawCount@ is -- equal to @1@, (@offset@ + -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand')) -- /must/ be less than or equal to the size of @buffer@ -- -- - #VUID-vkCmdDrawIndexedIndirect-drawCount-00540# 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) -- -- - #VUID-vkCmdDrawIndexedIndirect-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDrawIndexedIndirect-buffer-parameter# @buffer@ /must/ be -- a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdDrawIndexedIndirect-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDrawIndexedIndirect-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdDrawIndexedIndirect-renderpass# This command /must/ only -- be called inside of a render pass instance -- -- - #VUID-vkCmdDrawIndexedIndirect-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdDrawIndexedIndirect-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDrawIndexedIndirect CommandBuffer commandBuffer Buffer buffer "offset" ::: DeviceSize offset "firstViewport" ::: Word32 drawCount "firstViewport" ::: Word32 stride = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedIndirectPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDrawIndexedIndirect is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDrawIndexedIndirect" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdDispatch-magFilter-04553# 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' -- -- - #VUID-vkCmdDispatch-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_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' -- -- - #VUID-vkCmdDispatch-None-06479# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDispatch-None-02691# 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' -- -- - #VUID-vkCmdDispatch-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDispatch-None-02692# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDispatch-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDispatch-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDispatch-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDispatch-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDispatch-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDispatch-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDispatch-flags-02696# 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' -- -- - #VUID-vkCmdDispatch-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatch-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatch-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatch-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatch-None-08600# For each set /n/ that is statically -- used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatch-None-08601# For each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatch-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatch-None-08114# 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 and the bound -- 'Vulkan.Core10.Handles.Pipeline' was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatch-None-08115# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via 'cmdBindDescriptorSets', the bound -- 'Vulkan.Core10.Handles.Pipeline' /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatch-None-08116# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatch-None-08604# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDispatch-None-08117# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatch-None-08119# If a descriptor is dynamically used -- with a 'Vulkan.Core10.Handles.Pipeline' created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDispatch-None-08605# If a descriptor is dynamically used -- with a 'Vulkan.Extensions.Handles.ShaderEXT' created with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' that was created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDispatch-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDispatch-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDispatch-None-08608# If a pipeline is bound to the -- pipeline bind point used by this command, 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 -- -- - #VUID-vkCmdDispatch-None-08609# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatch-None-08610# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatch-None-08611# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatch-uniformBuffers-06935# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a uniform buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDispatch-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatch-storageBuffers-06936# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a storage buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDispatch-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatch-commandBuffer-02707# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDispatch-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDispatch-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDispatch-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDispatch-format-07753# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDispatch-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' 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 -- -- - #VUID-vkCmdDispatch-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDispatch-OpImageWrite-04469# 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 -- buffer view’s format -- -- - #VUID-vkCmdDispatch-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDispatch-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDispatch-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDispatch-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDispatch-sparseImageInt64Atomics-04474# 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 -- -- - #VUID-vkCmdDispatch-sparseImageInt64Atomics-04475# 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 -- -- - #VUID-vkCmdDispatch-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDispatch-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageWeightedSampleQCOM-06978# If any command -- other than @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ not have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatch-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDispatch-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDispatch-None-07288# Any shader invocation executed by -- this command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDispatch-commandBuffer-02712# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, 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 -- -- - #VUID-vkCmdDispatch-commandBuffer-02713# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, pipeline stages other than the framebuffer-space -- and compute stages in the 'Vulkan.Core10.Handles.Pipeline' object -- bound to the pipeline bind point used by this command /must/ not -- write to any resource -- -- - #VUID-vkCmdDispatch-commandBuffer-04617# If any of the shader stages -- of the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command uses the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirvenv-capabilities-table-RayQueryKHR RayQueryKHR> -- capability, then @commandBuffer@ /must/ not be a protected command -- buffer -- -- - #VUID-vkCmdDispatch-groupCountX-00386# @groupCountX@ /must/ be less -- than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0] -- -- - #VUID-vkCmdDispatch-groupCountY-00387# @groupCountY@ /must/ be less -- than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1] -- -- - #VUID-vkCmdDispatch-groupCountZ-00388# @groupCountZ@ /must/ be less -- than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2] -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdDispatch-commandBuffer-parameter# @commandBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDispatch-commandBuffer-recording# @commandBuffer@ /must/ -- be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDispatch-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - #VUID-vkCmdDispatch-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdDispatch-videocoding# This command /must/ only be called -- outside of a video coding scope -- -- == 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Compute | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDispatch CommandBuffer commandBuffer "firstViewport" ::: Word32 groupCountX "firstViewport" ::: Word32 groupCountY "firstViewport" ::: Word32 groupCountZ = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDispatchPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDispatch is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDispatch" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDispatchIndirect :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IO () -- | vkCmdDispatchIndirect - Dispatch compute work items with 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 -- -- - #VUID-vkCmdDispatchIndirect-magFilter-04553# 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' -- -- - #VUID-vkCmdDispatchIndirect-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_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' -- -- - #VUID-vkCmdDispatchIndirect-None-06479# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDispatchIndirect-None-02691# 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' -- -- - #VUID-vkCmdDispatchIndirect-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDispatchIndirect-None-02692# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDispatchIndirect-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDispatchIndirect-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDispatchIndirect-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.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' -- -- - #VUID-vkCmdDispatchIndirect-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDispatchIndirect-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-flags-02696# 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' -- -- - #VUID-vkCmdDispatchIndirect-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchIndirect-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchIndirect-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchIndirect-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchIndirect-None-08600# For each set /n/ that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatchIndirect-None-08601# For each push constant that -- is statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatchIndirect-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- 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' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatchIndirect-None-08114# 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 and the bound 'Vulkan.Core10.Handles.Pipeline' -- was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchIndirect-None-08115# If the descriptors used by -- the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point were specified via 'cmdBindDescriptorSets', the bound -- 'Vulkan.Core10.Handles.Pipeline' /must/ have been created without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchIndirect-None-08116# Descriptors in bound -- descriptor buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchIndirect-None-08604# Descriptors in bound -- descriptor buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDispatchIndirect-None-08117# If the descriptors used by -- the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchIndirect-None-08119# If a descriptor is -- dynamically used with a 'Vulkan.Core10.Handles.Pipeline' created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDispatchIndirect-None-08605# If a descriptor is -- dynamically used with a 'Vulkan.Extensions.Handles.ShaderEXT' -- created with a 'Vulkan.Core10.Handles.DescriptorSetLayout' that was -- created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDispatchIndirect-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDispatchIndirect-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDispatchIndirect-None-08608# If a pipeline is bound to -- the pipeline bind point used by this command, 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 -- -- - #VUID-vkCmdDispatchIndirect-None-08609# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatchIndirect-None-08610# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatchIndirect-None-08611# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatchIndirect-uniformBuffers-06935# If any stage of -- the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a uniform buffer, and that -- stage was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDispatchIndirect-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatchIndirect-storageBuffers-06936# If any stage of -- the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a storage buffer, and that -- stage was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDispatchIndirect-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- 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 -- -- - #VUID-vkCmdDispatchIndirect-commandBuffer-02707# If @commandBuffer@ -- is an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDispatchIndirect-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDispatchIndirect-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDispatchIndirect-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDispatchIndirect-format-07753# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDispatchIndirect-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' 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 -- -- - #VUID-vkCmdDispatchIndirect-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDispatchIndirect-OpImageWrite-04469# 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 -- buffer view’s format -- -- - #VUID-vkCmdDispatchIndirect-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDispatchIndirect-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDispatchIndirect-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDispatchIndirect-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component 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 -- -- - #VUID-vkCmdDispatchIndirect-sparseImageInt64Atomics-04474# 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 -- -- - #VUID-vkCmdDispatchIndirect-sparseImageInt64Atomics-04475# 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 -- -- - #VUID-vkCmdDispatchIndirect-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDispatchIndirect-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageWeightedSampleQCOM-06978# If any -- command other than @OpImageWeightedSampleQCOM@, -- @OpImageBoxFilterQCOM@, @OpImageBlockMatchWindowSSDQCOM@, -- @OpImageBlockMatchWindowSADQCOM@, @OpImageBlockMatchGatherSSDQCOM@, -- @OpImageBlockMatchGatherSADQCOM@, @OpImageBlockMatchSSDQCOM@, or -- @OpImageBlockMatchSADQCOM@ uses a 'Vulkan.Core10.Handles.Sampler' as -- a result of this command, then the sampler /must/ not have been -- created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- '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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchIndirect-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDispatchIndirect-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDispatchIndirect-None-07288# Any shader invocation -- executed by this command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDispatchIndirect-buffer-02708# If @buffer@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdDispatchIndirect-buffer-02709# @buffer@ /must/ have been -- created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT' -- bit set -- -- - #VUID-vkCmdDispatchIndirect-offset-02710# @offset@ /must/ be a -- multiple of @4@ -- -- - #VUID-vkCmdDispatchIndirect-commandBuffer-02711# @commandBuffer@ -- /must/ not be a protected command buffer -- -- - #VUID-vkCmdDispatchIndirect-offset-00407# 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) -- -- - #VUID-vkCmdDispatchIndirect-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDispatchIndirect-buffer-parameter# @buffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdDispatchIndirect-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDispatchIndirect-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - #VUID-vkCmdDispatchIndirect-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdDispatchIndirect-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdDispatchIndirect-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Compute | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> io () cmdDispatchIndirect CommandBuffer commandBuffer Buffer buffer "offset" ::: DeviceSize offset = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) vkCmdDispatchIndirectPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDispatchIndirect is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDispatchIndirect" (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO () vkCmdDispatchIndirect' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer buffer) ("offset" ::: DeviceSize offset)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 source region specified by @pRegions@ is copied from the source -- buffer to the destination region of the destination buffer. If any of -- the specified regions in @srcBuffer@ overlaps in memory with any of the -- specified regions in @dstBuffer@, values read from those overlapping -- regions are undefined. -- -- == Valid Usage -- -- - #VUID-vkCmdCopyBuffer-commandBuffer-01822# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @srcBuffer@ /must/ not be a protected buffer -- -- - #VUID-vkCmdCopyBuffer-commandBuffer-01823# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be a protected buffer -- -- - #VUID-vkCmdCopyBuffer-commandBuffer-01824# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be an unprotected buffer -- -- - #VUID-vkCmdCopyBuffer-srcOffset-00113# The @srcOffset@ member of -- each element of @pRegions@ /must/ be less than the size of -- @srcBuffer@ -- -- - #VUID-vkCmdCopyBuffer-dstOffset-00114# The @dstOffset@ member of -- each element of @pRegions@ /must/ be less than the size of -- @dstBuffer@ -- -- - #VUID-vkCmdCopyBuffer-size-00115# The @size@ member of each element -- of @pRegions@ /must/ be less than or equal to the size of -- @srcBuffer@ minus @srcOffset@ -- -- - #VUID-vkCmdCopyBuffer-size-00116# The @size@ member of each element -- of @pRegions@ /must/ be less than or equal to the size of -- @dstBuffer@ minus @dstOffset@ -- -- - #VUID-vkCmdCopyBuffer-pRegions-00117# The union of the source -- regions, and the union of the destination regions, specified by the -- elements of @pRegions@, /must/ not overlap in memory -- -- - #VUID-vkCmdCopyBuffer-srcBuffer-00118# @srcBuffer@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - #VUID-vkCmdCopyBuffer-srcBuffer-00119# If @srcBuffer@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyBuffer-dstBuffer-00120# @dstBuffer@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdCopyBuffer-dstBuffer-00121# If @dstBuffer@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdCopyBuffer-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdCopyBuffer-srcBuffer-parameter# @srcBuffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdCopyBuffer-dstBuffer-parameter# @dstBuffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdCopyBuffer-pRegions-parameter# @pRegions@ /must/ be a -- valid pointer to an array of @regionCount@ valid 'BufferCopy' -- structures -- -- - #VUID-vkCmdCopyBuffer-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdCopyBuffer-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - #VUID-vkCmdCopyBuffer-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdCopyBuffer-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdCopyBuffer-regionCount-arraylength# @regionCount@ /must/ -- be greater than @0@ -- -- - #VUID-vkCmdCopyBuffer-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> Buffer -> ("regions" ::: Vector BufferCopy) -> io () cmdCopyBuffer CommandBuffer commandBuffer Buffer srcBuffer Buffer dstBuffer "regions" ::: Vector BufferCopy regions = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) vkCmdCopyBufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdCopyBuffer is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @BufferCopy ((forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector BufferCopy regions)) forall a. Num a => a -> a -> a * Int 24) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i BufferCopy e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRegions" ::: Ptr BufferCopy pPRegions forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr BufferCopy) (BufferCopy e)) ("regions" ::: Vector BufferCopy regions) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdCopyBuffer" (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO () vkCmdCopyBuffer' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer srcBuffer) (Buffer dstBuffer) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector BufferCopy regions)) :: Word32)) ("pRegions" ::: Ptr BufferCopy pPRegions)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 source region specified by @pRegions@ is copied from the source -- image to the destination region of the destination image. If any of the -- specified regions in @srcImage@ overlaps in memory with any of the -- specified regions in @dstImage@, values read from those overlapping -- regions are undefined. -- -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion Multi-planar images> -- /can/ only be copied on a per-plane basis, and the subresources used in -- each region when copying to or from such images /must/ specify only one -- plane, though different regions /can/ specify different planes. When -- copying planes of multi-planar images, the format considered is the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatible-planes compatible format for that plane>, -- rather than the format of the multi-planar image. -- -- If the format of the destination image has a different -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatibility-classes block extent> -- than the source image (e.g. one is a compressed format), the offset and -- extent for each of the regions specified is -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-size-compatibility scaled according to the block extents of each format> -- to match in size. Copy regions for each image /must/ be aligned to a -- multiple of the texel block extent in each dimension, except at the -- edges of the image, where region extents /must/ match the edge of the -- image. -- -- 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; @depth@ -- slices in the 3D image correspond to @layerCount@ layers in the 2D -- image, with an effective @depth@ of @1@ used for the 2D image. If -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is enabled, all other combinations are allowed and function as if 1D -- images are 2D images with a height of 1. Otherwise, other combinations -- of image types are disallowed. -- -- == Valid Usage -- -- - #VUID-vkCmdCopyImage-commandBuffer-01825# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @srcImage@ /must/ not be a protected image -- -- - #VUID-vkCmdCopyImage-commandBuffer-01826# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be a protected image -- -- - #VUID-vkCmdCopyImage-commandBuffer-01827# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be an unprotected image -- -- - #VUID-vkCmdCopyImage-pRegions-00124# The union of all source -- regions, and the union of all destination regions, specified by the -- elements of @pRegions@, /must/ not overlap in memory -- -- - #VUID-vkCmdCopyImage-srcImage-01995# 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' -- -- - #VUID-vkCmdCopyImage-srcImageLayout-00128# @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' -- -- - #VUID-vkCmdCopyImage-srcImageLayout-01917# @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' -- -- - #VUID-vkCmdCopyImage-dstImage-01996# 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' -- -- - #VUID-vkCmdCopyImage-dstImageLayout-00133# @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' -- -- - #VUID-vkCmdCopyImage-dstImageLayout-01395# @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' -- -- - #VUID-vkCmdCopyImage-srcImage-01548# 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 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-size-compatibility size-compatible> -- -- - #VUID-vkCmdCopyImage-None-01549# 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 -- -- - #VUID-vkCmdCopyImage-srcImage-09247# If the -- 'Vulkan.Core10.Enums.Format.Format' of each of @srcImage@ and -- @dstImage@ is a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#compressed_image_formats compressed image format>, -- the formats /must/ have the same texel block extent -- -- - #VUID-vkCmdCopyImage-srcImage-00136# The sample count of @srcImage@ -- and @dstImage@ /must/ match -- -- - #VUID-vkCmdCopyImage-srcOffset-01783# 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' -- -- - #VUID-vkCmdCopyImage-dstOffset-01784# 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' -- -- - #VUID-vkCmdCopyImage-srcImage-01551# 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 -- -- - #VUID-vkCmdCopyImage-srcImage-08713# 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>, -- then for each element of @pRegions@, @srcSubresource.aspectMask@ -- /must/ be a single valid -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-planes-image-aspect multi-planar aspect mask> -- bit -- -- - #VUID-vkCmdCopyImage-dstImage-08714# 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>, -- then for each element of @pRegions@, @dstSubresource.aspectMask@ -- /must/ be a single valid -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-planes-image-aspect multi-planar aspect mask> -- bit -- -- - #VUID-vkCmdCopyImage-srcImage-01556# 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' -- -- - #VUID-vkCmdCopyImage-dstImage-01557# 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' -- -- - #VUID-vkCmdCopyImage-apiVersion-07932# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_maintenance1 VK_KHR_maintenance1> -- extension is not enabled, or -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties'::@apiVersion@ -- is less than Vulkan 1.1, and 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/ both be @0@, and -- @srcSubresource.layerCount@ and @dstSubresource.layerCount@ /must/ -- both be @1@ -- -- - #VUID-vkCmdCopyImage-srcImage-04443# If @srcImage@ is 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@ -- -- - #VUID-vkCmdCopyImage-dstImage-04444# If @dstImage@ is 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@ -- -- - #VUID-vkCmdCopyImage-aspectMask-00142# For each element of -- @pRegions@, @srcSubresource.aspectMask@ /must/ specify aspects -- present in @srcImage@ -- -- - #VUID-vkCmdCopyImage-aspectMask-00143# For each element of -- @pRegions@, @dstSubresource.aspectMask@ /must/ specify aspects -- present in @dstImage@ -- -- - #VUID-vkCmdCopyImage-srcOffset-00144# 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@ -- -- - #VUID-vkCmdCopyImage-srcOffset-00145# 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@ -- -- - #VUID-vkCmdCopyImage-srcImage-00146# 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@ -- -- - #VUID-vkCmdCopyImage-srcOffset-00147# If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then 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@ -- -- - #VUID-vkCmdCopyImage-srcImage-01785# 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@ -- -- - #VUID-vkCmdCopyImage-dstImage-01786# 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@ -- -- - #VUID-vkCmdCopyImage-srcImage-01787# If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element -- of @pRegions@, @srcOffset.z@ /must/ be @0@ -- -- - #VUID-vkCmdCopyImage-dstImage-01788# If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element -- of @pRegions@, @dstOffset.z@ /must/ be @0@ -- -- - #VUID-vkCmdCopyImage-apiVersion-07933# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_maintenance1 VK_KHR_maintenance1> -- extension is not enabled, and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties'::@apiVersion@ -- is less than Vulkan 1.1, @srcImage@ and @dstImage@ /must/ have the -- same 'Vulkan.Core10.Enums.ImageType.ImageType' -- -- - #VUID-vkCmdCopyImage-apiVersion-08969# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_maintenance1 VK_KHR_maintenance1> -- extension is not enabled, and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties'::@apiVersion@ -- is less than Vulkan 1.1, @srcImage@ or @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element -- of @pRegions@, @extent.depth@ /must/ be @1@ -- -- - #VUID-vkCmdCopyImage-srcImage-07743# If @srcImage@ and @dstImage@ -- have a different 'Vulkan.Core10.Enums.ImageType.ImageType', and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, one /must/ be -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' and the other /must/ -- be 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' -- -- - #VUID-vkCmdCopyImage-srcImage-08793# If @srcImage@ and @dstImage@ -- have the same 'Vulkan.Core10.Enums.ImageType.ImageType', for each -- element of @pRegions@, if neither of the @layerCount@ members of -- @srcSubresource@ or @dstSubresource@ are -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the -- @layerCount@ members of @srcSubresource@ or @dstSubresource@ /must/ -- match -- -- - #VUID-vkCmdCopyImage-maintenance5-08792# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- feature is not enabled, the @layerCount@ member of @srcSubresource@ -- or @dstSubresource@ /must/ not be -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' -- -- - #VUID-vkCmdCopyImage-srcImage-08794# If @srcImage@ and @dstImage@ -- have the same 'Vulkan.Core10.Enums.ImageType.ImageType', and one of -- the @layerCount@ members of @srcSubresource@ or @dstSubresource@ is -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the other -- member /must/ be either -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' or equal to the -- @arrayLayers@ member of the 'Vulkan.Core10.Image.ImageCreateInfo' -- used to create the image minus @baseArrayLayer@ -- -- - #VUID-vkCmdCopyImage-srcImage-01790# 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@ -- -- - #VUID-vkCmdCopyImage-srcImage-01791# 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@ -- -- - #VUID-vkCmdCopyImage-dstImage-01792# 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@ -- -- - #VUID-vkCmdCopyImage-dstOffset-00150# 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@ -- -- - #VUID-vkCmdCopyImage-dstOffset-00151# 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@ -- -- - #VUID-vkCmdCopyImage-dstImage-00152# 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@ -- -- - #VUID-vkCmdCopyImage-dstOffset-00153# If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then 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@ -- -- - #VUID-vkCmdCopyImage-pRegions-07278# For each element of @pRegions@, -- @srcOffset.x@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImage-pRegions-07279# For each element of @pRegions@, -- @srcOffset.y@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImage-pRegions-07280# For each element of @pRegions@, -- @srcOffset.z@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImage-pRegions-07281# For each element of @pRegions@, -- @dstOffset.x@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyImage-pRegions-07282# For each element of @pRegions@, -- @dstOffset.y@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyImage-pRegions-07283# For each element of @pRegions@, -- @dstOffset.z@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyImage-srcImage-01728# For each element of @pRegions@, -- if the sum of @srcOffset.x@ and @extent.width@ does not equal the -- width of the subresource specified by @srcSubresource@, -- @extent.width@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImage-srcImage-01729# For each element of @pRegions@, -- if the sum of @srcOffset.y@ and @extent.height@ does not equal the -- height of the subresource specified by @srcSubresource@, -- @extent.height@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImage-srcImage-01730# For each element of @pRegions@, -- if the sum of @srcOffset.z@ and @extent.depth@ does not equal the -- depth of the subresource specified by @srcSubresource@, -- @extent.depth@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImage-dstImage-01732# For each element of @pRegions@, -- if the sum of @dstOffset.x@ and @extent.width@ does not equal the -- width of the subresource specified by @dstSubresource@, -- @extent.width@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyImage-dstImage-01733# For each element of @pRegions@, -- if the sum of @dstOffset.y@ and @extent.height@ does not equal the -- height of the subresource specified by @dstSubresource@, -- @extent.height@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyImage-dstImage-01734# For each element of @pRegions@, -- if the sum of @dstOffset.z@ and @extent.depth@ does not equal the -- depth of the subresource specified by @dstSubresource@, -- @extent.depth@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyImage-aspect-06662# If the @aspect@ member of any -- element of @pRegions@ includes any flag other than -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' -- or @srcImage@ was not created with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkImageStencilUsageCreateInfo separate stencil usage>, -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT' -- /must/ have been included in the -- 'Vulkan.Core10.Image.ImageCreateInfo'::@usage@ used to create -- @srcImage@ -- -- - #VUID-vkCmdCopyImage-aspect-06663# If the @aspect@ member of any -- element of @pRegions@ includes any flag other than -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' -- or @dstImage@ was not created with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkImageStencilUsageCreateInfo 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 -- @dstImage@ -- -- - #VUID-vkCmdCopyImage-aspect-06664# If the @aspect@ member of any -- element of @pRegions@ includes -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', -- and @srcImage@ was created with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkImageStencilUsageCreateInfo separate stencil usage>, -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT' -- /must/ have been included in the -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo'::@stencilUsage@ -- used to create @srcImage@ -- -- - #VUID-vkCmdCopyImage-aspect-06665# If the @aspect@ member of any -- element of @pRegions@ includes -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', -- and @dstImage@ was created with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkImageStencilUsageCreateInfo 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 @dstImage@ -- -- - #VUID-vkCmdCopyImage-srcImage-07966# If @srcImage@ is non-sparse -- then the image or the specified /disjoint/ plane /must/ be bound -- completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyImage-srcSubresource-07967# 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 -- -- - #VUID-vkCmdCopyImage-srcSubresource-07968# The -- @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of -- each element of @pRegions@ , if @srcSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ -- was created -- -- - #VUID-vkCmdCopyImage-srcImage-07969# @srcImage@ /must/ not have been -- created with @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - #VUID-vkCmdCopyImage-dstImage-07966# If @dstImage@ is non-sparse -- then the image or the specified /disjoint/ plane /must/ be bound -- completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyImage-dstSubresource-07967# 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 -- -- - #VUID-vkCmdCopyImage-dstSubresource-07968# The -- @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of -- each element of @pRegions@ , if @dstSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ -- was created -- -- - #VUID-vkCmdCopyImage-dstImage-07969# @dstImage@ /must/ not have been -- created with @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdCopyImage-commandBuffer-parameter# @commandBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdCopyImage-srcImage-parameter# @srcImage@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdCopyImage-srcImageLayout-parameter# @srcImageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdCopyImage-dstImage-parameter# @dstImage@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdCopyImage-dstImageLayout-parameter# @dstImageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdCopyImage-pRegions-parameter# @pRegions@ /must/ be a -- valid pointer to an array of @regionCount@ valid 'ImageCopy' -- structures -- -- - #VUID-vkCmdCopyImage-commandBuffer-recording# @commandBuffer@ /must/ -- be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdCopyImage-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - #VUID-vkCmdCopyImage-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdCopyImage-videocoding# This command /must/ only be called -- outside of a video coding scope -- -- - #VUID-vkCmdCopyImage-regionCount-arraylength# @regionCount@ /must/ -- be greater than @0@ -- -- - #VUID-vkCmdCopyImage-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("regions" ::: Vector ImageCopy) -> io () cmdCopyImage CommandBuffer commandBuffer "srcImage" ::: Image srcImage "srcImageLayout" ::: ImageLayout srcImageLayout "srcImage" ::: Image dstImage "srcImageLayout" ::: ImageLayout dstImageLayout "regions" ::: Vector ImageCopy regions = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr ImageCopy) -> IO ()) vkCmdCopyImagePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdCopyImage is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ImageCopy ((forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector ImageCopy regions)) forall a. Num a => a -> a -> a * Int 68) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ImageCopy e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRegions" ::: Ptr ImageCopy pPRegions forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 68 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageCopy) (ImageCopy e)) ("regions" ::: Vector ImageCopy regions) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdCopyImage" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector ImageCopy regions)) :: Word32)) ("pRegions" ::: Ptr ImageCopy pPRegions)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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, scaled 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 -- -- - #VUID-vkCmdBlitImage-commandBuffer-01834# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @srcImage@ /must/ not be a protected image -- -- - #VUID-vkCmdBlitImage-commandBuffer-01835# If @commandBuffer@ is an -- unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be a protected image -- -- - #VUID-vkCmdBlitImage-commandBuffer-01836# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be an unprotected image -- -- - #VUID-vkCmdBlitImage-pRegions-00215# The source region specified by -- each element of @pRegions@ /must/ be a region that is contained -- within @srcImage@ -- -- - #VUID-vkCmdBlitImage-pRegions-00216# The destination region -- specified by each element of @pRegions@ /must/ be a region that is -- contained within @dstImage@ -- -- - #VUID-vkCmdBlitImage-pRegions-00217# 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 -- -- - #VUID-vkCmdBlitImage-srcImage-01999# 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' -- -- - #VUID-vkCmdBlitImage-srcImage-06421# @srcImage@ /must/ not use a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion format that requires a sampler Y′CBCR conversion> -- -- - #VUID-vkCmdBlitImage-srcImage-00219# @srcImage@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - #VUID-vkCmdBlitImage-srcImage-00220# If @srcImage@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdBlitImage-srcImageLayout-00221# @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' -- -- - #VUID-vkCmdBlitImage-srcImageLayout-01398# @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' -- -- - #VUID-vkCmdBlitImage-dstImage-02000# 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' -- -- - #VUID-vkCmdBlitImage-dstImage-06422# @dstImage@ /must/ not use a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion format that requires a sampler Y′CBCR conversion> -- -- - #VUID-vkCmdBlitImage-dstImage-00224# @dstImage@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdBlitImage-dstImage-00225# If @dstImage@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdBlitImage-dstImageLayout-00226# @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' -- -- - #VUID-vkCmdBlitImage-dstImageLayout-01399# @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' -- -- - #VUID-vkCmdBlitImage-srcImage-00229# 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' -- -- - #VUID-vkCmdBlitImage-srcImage-00230# 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' -- -- - #VUID-vkCmdBlitImage-srcImage-00231# If either of @srcImage@ or -- @dstImage@ was created with a depth\/stencil format, the other -- /must/ have exactly the same format -- -- - #VUID-vkCmdBlitImage-srcImage-00232# If @srcImage@ was created with -- a depth\/stencil format, @filter@ /must/ be -- 'Vulkan.Core10.Enums.Filter.FILTER_NEAREST' -- -- - #VUID-vkCmdBlitImage-srcImage-00233# @srcImage@ /must/ have been -- created with a @samples@ value of -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdBlitImage-dstImage-00234# @dstImage@ /must/ have been -- created with a @samples@ value of -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdBlitImage-filter-02001# 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' -- -- - #VUID-vkCmdBlitImage-filter-02002# If @filter@ is -- 'Vulkan.Core10.Enums.Filter.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.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdBlitImage-filter-00237# If @filter@ is -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT', @srcImage@ /must/ be -- of type 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' -- -- - #VUID-vkCmdBlitImage-srcSubresource-01705# 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 -- -- - #VUID-vkCmdBlitImage-dstSubresource-01706# 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 -- -- - #VUID-vkCmdBlitImage-srcSubresource-01707# The -- @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of -- each element of @pRegions@ , if @srcSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ -- was created -- -- - #VUID-vkCmdBlitImage-dstSubresource-01708# The -- @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of -- each element of @pRegions@ , if @srcSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ -- was created -- -- - #VUID-vkCmdBlitImage-dstImage-02545# @dstImage@ and @srcImage@ -- /must/ not have been created with @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - #VUID-vkCmdBlitImage-srcImage-00240# 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@ -- -- - #VUID-vkCmdBlitImage-aspectMask-00241# For each element of -- @pRegions@, @srcSubresource.aspectMask@ /must/ specify aspects -- present in @srcImage@ -- -- - #VUID-vkCmdBlitImage-aspectMask-00242# For each element of -- @pRegions@, @dstSubresource.aspectMask@ /must/ specify aspects -- present in @dstImage@ -- -- - #VUID-vkCmdBlitImage-srcOffset-00243# For each element of -- @pRegions@, @srcOffsets@[0].x and @srcOffsets@[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@ -- -- - #VUID-vkCmdBlitImage-srcOffset-00244# For each element of -- @pRegions@, @srcOffsets@[0].y and @srcOffsets@[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@ -- -- - #VUID-vkCmdBlitImage-srcImage-00245# If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element -- of @pRegions@, @srcOffsets@[0].y /must/ be @0@ and @srcOffsets@[1].y -- /must/ be @1@ -- -- - #VUID-vkCmdBlitImage-srcOffset-00246# For each element of -- @pRegions@, @srcOffsets@[0].z and @srcOffsets@[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@ -- -- - #VUID-vkCmdBlitImage-srcImage-00247# 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@, @srcOffsets@[0].z /must/ be @0@ and @srcOffsets@[1].z -- /must/ be @1@ -- -- - #VUID-vkCmdBlitImage-dstOffset-00248# For each element of -- @pRegions@, @dstOffsets@[0].x and @dstOffsets@[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@ -- -- - #VUID-vkCmdBlitImage-dstOffset-00249# For each element of -- @pRegions@, @dstOffsets@[0].y and @dstOffsets@[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@ -- -- - #VUID-vkCmdBlitImage-dstImage-00250# If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element -- of @pRegions@, @dstOffsets@[0].y /must/ be @0@ and @dstOffsets@[1].y -- /must/ be @1@ -- -- - #VUID-vkCmdBlitImage-dstOffset-00251# For each element of -- @pRegions@, @dstOffsets@[0].z and @dstOffsets@[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@ -- -- - #VUID-vkCmdBlitImage-dstImage-00252# 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@, @dstOffsets@[0].z /must/ be @0@ and @dstOffsets@[1].z -- /must/ be @1@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdBlitImage-commandBuffer-parameter# @commandBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBlitImage-srcImage-parameter# @srcImage@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdBlitImage-srcImageLayout-parameter# @srcImageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdBlitImage-dstImage-parameter# @dstImage@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdBlitImage-dstImageLayout-parameter# @dstImageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdBlitImage-pRegions-parameter# @pRegions@ /must/ be a -- valid pointer to an array of @regionCount@ valid 'ImageBlit' -- structures -- -- - #VUID-vkCmdBlitImage-filter-parameter# @filter@ /must/ be a valid -- 'Vulkan.Core10.Enums.Filter.Filter' value -- -- - #VUID-vkCmdBlitImage-commandBuffer-recording# @commandBuffer@ /must/ -- be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBlitImage-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBlitImage-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdBlitImage-videocoding# This command /must/ only be called -- outside of a video coding scope -- -- - #VUID-vkCmdBlitImage-regionCount-arraylength# @regionCount@ /must/ -- be greater than @0@ -- -- - #VUID-vkCmdBlitImage-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("regions" ::: Vector ImageBlit) -> Filter -> io () cmdBlitImage CommandBuffer commandBuffer "srcImage" ::: Image srcImage "srcImageLayout" ::: ImageLayout srcImageLayout "srcImage" ::: Image dstImage "srcImageLayout" ::: ImageLayout dstImageLayout "regions" ::: Vector ImageBlit regions Filter filter' = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr ImageBlit) -> Filter -> IO ()) vkCmdBlitImagePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBlitImage is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ImageBlit ((forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector ImageBlit regions)) forall a. Num a => a -> a -> a * Int 80) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ImageBlit e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRegions" ::: Ptr ImageBlit pPRegions forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 80 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageBlit) (ImageBlit e)) ("regions" ::: Vector ImageBlit regions) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBlitImage" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector ImageBlit regions)) :: Word32)) ("pRegions" ::: Ptr ImageBlit pPRegions) (Filter filter')) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 source region specified by @pRegions@ is copied from the source -- buffer to the destination region of the destination image according to -- the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#copies-buffers-images-addressing addressing calculations> -- for each resource. If any of the specified regions in @srcBuffer@ -- overlaps in memory with any of the specified regions in @dstImage@, -- values read from those overlapping regions are undefined. If any region -- accesses a depth aspect in @dstImage@ and the -- @VK_EXT_depth_range_unrestricted@ extension is not enabled, values -- copied from @srcBuffer@ outside of the range [0,1] will be be written as -- undefined values to the destination image. -- -- Copy regions for the image /must/ be aligned to a multiple of the texel -- block extent in each dimension, except at the edges of the image, where -- region extents /must/ match the edge of the image. -- -- == Valid Usage -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07966# If @dstImage@ is -- non-sparse then the image or the specified /disjoint/ plane /must/ -- be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyBufferToImage-imageSubresource-07967# 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 -- -- - #VUID-vkCmdCopyBufferToImage-imageSubresource-07968# The -- @imageSubresource.baseArrayLayer@ + @imageSubresource.layerCount@ of -- each element of @pRegions@ , if @imageSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ -- was created -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07969# @dstImage@ /must/ not -- have been created with @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - #VUID-vkCmdCopyBufferToImage-imageSubresource-07970# The image -- region specified by each element of @pRegions@ /must/ be contained -- within the specified @imageSubresource@ of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-imageSubresource-07971# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-imageSubresource-07972# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07973# @dstImage@ /must/ have -- a sample count equal to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-01828# If @commandBuffer@ -- is an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @srcBuffer@ /must/ not be a protected buffer -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-01829# If @commandBuffer@ -- is an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be a protected image -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-01830# If @commandBuffer@ -- is a protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be an unprotected image -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-07737# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-imageOffset-07738# 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' -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-07739# 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' -- -- - #VUID-vkCmdCopyBufferToImage-pRegions-00171# @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@ -- -- - #VUID-vkCmdCopyBufferToImage-pRegions-00173# The union of all source -- regions, and the union of all destination regions, specified by the -- elements of @pRegions@, /must/ not overlap in memory -- -- - #VUID-vkCmdCopyBufferToImage-srcBuffer-00174# @srcBuffer@ /must/ -- have been created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-01997# 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' -- -- - #VUID-vkCmdCopyBufferToImage-srcBuffer-00176# If @srcBuffer@ is -- non-sparse then it /must/ be bound completely and contiguously to a -- single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-00177# @dstImage@ /must/ have -- been created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdCopyBufferToImage-dstImageLayout-00180# @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' -- -- - #VUID-vkCmdCopyBufferToImage-dstImageLayout-01396# @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' -- -- - #VUID-vkCmdCopyBufferToImage-pRegions-07931# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_depth_range_unrestricted VK_EXT_depth_range_unrestricted> -- is not enabled, for each element of @pRegions@ whose -- @imageSubresource@ contains a depth aspect, the data in @srcBuffer@ -- /must/ be in the range [0,1] -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07979# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-imageOffset-09104# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07980# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07274# For each element of -- @pRegions@, @imageOffset.x@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07275# For each element of -- @pRegions@, @imageOffset.y@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07276# For each element of -- @pRegions@, @imageOffset.z@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-00207# For each element of -- @pRegions@, if the sum of @imageOffset.x@ and @extent.width@ does -- not equal the width of the subresource specified by -- @srcSubresource@, @extent.width@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-00208# For each element of -- @pRegions@, if the sum of @imageOffset.y@ and @extent.height@ does -- not equal the height of the subresource specified by -- @srcSubresource@, @extent.height@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-00209# For each element of -- @pRegions@, if the sum of @imageOffset.z@ and @extent.depth@ does -- not equal the depth of the subresource specified by -- @srcSubresource@, @extent.depth@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-imageSubresource-09105# For each -- element of @pRegions@, @imageSubresource.aspectMask@ /must/ specify -- aspects present in @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07981# 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>, -- then for each element of @pRegions@, @imageSubresource.aspectMask@ -- /must/ be a single valid -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-planes-image-aspect multi-planar aspect mask> -- bit -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07983# 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@ -- -- - #VUID-vkCmdCopyBufferToImage-bufferRowLength-09106# For each element -- of @pRegions@, @bufferRowLength@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-bufferImageHeight-09107# For each -- element of @pRegions@, @bufferImageHeight@ /must/ be a multiple of -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @dstImage@ -- -- - #VUID-vkCmdCopyBufferToImage-bufferRowLength-09108# For each element -- of @pRegions@, @bufferRowLength@ divided by the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- and then multiplied by the texel block size of @dstImage@ /must/ be -- less than or equal to 231-1 -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07975# If @dstImage@ does not -- have either a depth\/stencil format 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 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block size> -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07976# 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 ???> -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-07978# If @dstImage@ has a -- depth\/stencil format, the @bufferOffset@ member of any element of -- @pRegions@ /must/ be a multiple of @4@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdCopyBufferToImage-srcBuffer-parameter# @srcBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdCopyBufferToImage-dstImage-parameter# @dstImage@ /must/ -- be a valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdCopyBufferToImage-dstImageLayout-parameter# -- @dstImageLayout@ /must/ be a valid -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value -- -- - #VUID-vkCmdCopyBufferToImage-pRegions-parameter# @pRegions@ /must/ -- be a valid pointer to an array of @regionCount@ valid -- 'BufferImageCopy' structures -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdCopyBufferToImage-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - #VUID-vkCmdCopyBufferToImage-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdCopyBufferToImage-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdCopyBufferToImage-regionCount-arraylength# @regionCount@ -- /must/ be greater than @0@ -- -- - #VUID-vkCmdCopyBufferToImage-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("regions" ::: Vector BufferImageCopy) -> io () cmdCopyBufferToImage CommandBuffer commandBuffer Buffer srcBuffer "srcImage" ::: Image dstImage "srcImageLayout" ::: ImageLayout dstImageLayout "regions" ::: Vector BufferImageCopy regions = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferImageCopy) -> IO ()) vkCmdCopyBufferToImagePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdCopyBufferToImage is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @BufferImageCopy ((forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector BufferImageCopy regions)) forall a. Num a => a -> a -> a * Int 56) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i BufferImageCopy e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRegions" ::: Ptr BufferImageCopy pPRegions forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 56 forall a. Num a => a -> a -> a * (Int i)) :: Ptr BufferImageCopy) (BufferImageCopy e)) ("regions" ::: Vector BufferImageCopy regions) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdCopyBufferToImage" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector BufferImageCopy regions)) :: Word32)) ("pRegions" ::: Ptr BufferImageCopy pPRegions)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 source region specified by @pRegions@ is copied from the source -- image to the destination region of the destination buffer according to -- the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#copies-buffers-images-addressing addressing calculations> -- for each resource. If any of the specified regions in @srcImage@ -- overlaps in memory with any of the specified regions in @dstBuffer@, -- values read from those overlapping regions are undefined. -- -- Copy regions for the image /must/ be aligned to a multiple of the texel -- block extent in each dimension, except at the edges of the image, where -- region extents /must/ match the edge of the image. -- -- == Valid Usage -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07966# If @srcImage@ is -- non-sparse then the image or the specified /disjoint/ plane /must/ -- be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyImageToBuffer-imageSubresource-07967# 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 -- -- - #VUID-vkCmdCopyImageToBuffer-imageSubresource-07968# The -- @imageSubresource.baseArrayLayer@ + @imageSubresource.layerCount@ of -- each element of @pRegions@ , if @imageSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ -- was created -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07969# @srcImage@ /must/ not -- have been created with @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - #VUID-vkCmdCopyImageToBuffer-imageSubresource-07970# The image -- region specified by each element of @pRegions@ /must/ be contained -- within the specified @imageSubresource@ of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-imageSubresource-07971# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-imageSubresource-07972# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07973# @srcImage@ /must/ have -- a sample count equal to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-01831# If @commandBuffer@ -- is an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @srcImage@ /must/ not be a protected image -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-01832# If @commandBuffer@ -- is an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be a protected buffer -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-01833# If @commandBuffer@ -- is a protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be an unprotected buffer -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-07746# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-imageOffset-07747# 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' -- -- - #VUID-vkCmdCopyImageToBuffer-pRegions-00183# @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@ -- -- - #VUID-vkCmdCopyImageToBuffer-pRegions-00184# The union of all source -- regions, and the union of all destination regions, specified by the -- elements of @pRegions@, /must/ not overlap in memory -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-00186# @srcImage@ /must/ have -- been created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-01998# 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' -- -- - #VUID-vkCmdCopyImageToBuffer-dstBuffer-00191# @dstBuffer@ /must/ -- have been created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdCopyImageToBuffer-dstBuffer-00192# If @dstBuffer@ is -- non-sparse then it /must/ be bound completely and contiguously to a -- single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyImageToBuffer-srcImageLayout-00189# @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' -- -- - #VUID-vkCmdCopyImageToBuffer-srcImageLayout-01397# @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' -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07979# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-imageOffset-09104# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07980# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07274# For each element of -- @pRegions@, @imageOffset.x@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07275# For each element of -- @pRegions@, @imageOffset.y@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07276# For each element of -- @pRegions@, @imageOffset.z@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-00207# For each element of -- @pRegions@, if the sum of @imageOffset.x@ and @extent.width@ does -- not equal the width of the subresource specified by -- @srcSubresource@, @extent.width@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-00208# For each element of -- @pRegions@, if the sum of @imageOffset.y@ and @extent.height@ does -- not equal the height of the subresource specified by -- @srcSubresource@, @extent.height@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-00209# For each element of -- @pRegions@, if the sum of @imageOffset.z@ and @extent.depth@ does -- not equal the depth of the subresource specified by -- @srcSubresource@, @extent.depth@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent depth> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-imageSubresource-09105# For each -- element of @pRegions@, @imageSubresource.aspectMask@ /must/ specify -- aspects present in @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07981# 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>, -- then for each element of @pRegions@, @imageSubresource.aspectMask@ -- /must/ be a single valid -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-planes-image-aspect multi-planar aspect mask> -- bit -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07983# 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@ -- -- - #VUID-vkCmdCopyImageToBuffer-bufferRowLength-09106# For each element -- of @pRegions@, @bufferRowLength@ /must/ be a multiple of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-bufferImageHeight-09107# For each -- element of @pRegions@, @bufferImageHeight@ /must/ be a multiple of -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent height> -- of the 'Vulkan.Core10.Enums.Format.Format' of @srcImage@ -- -- - #VUID-vkCmdCopyImageToBuffer-bufferRowLength-09108# For each element -- of @pRegions@, @bufferRowLength@ divided by the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block extent width> -- and then multiplied by the texel block size of @srcImage@ /must/ be -- less than or equal to 231-1 -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07975# If @srcImage@ does not -- have either a depth\/stencil format 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 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility-classes texel block size> -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07976# 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 ???> -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-07978# If @srcImage@ has a -- depth\/stencil format, the @bufferOffset@ member of any element of -- @pRegions@ /must/ be a multiple of @4@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdCopyImageToBuffer-srcImage-parameter# @srcImage@ /must/ -- be a valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdCopyImageToBuffer-srcImageLayout-parameter# -- @srcImageLayout@ /must/ be a valid -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value -- -- - #VUID-vkCmdCopyImageToBuffer-dstBuffer-parameter# @dstBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdCopyImageToBuffer-pRegions-parameter# @pRegions@ /must/ -- be a valid pointer to an array of @regionCount@ valid -- 'BufferImageCopy' structures -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdCopyImageToBuffer-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - #VUID-vkCmdCopyImageToBuffer-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdCopyImageToBuffer-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdCopyImageToBuffer-regionCount-arraylength# @regionCount@ -- /must/ be greater than @0@ -- -- - #VUID-vkCmdCopyImageToBuffer-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> Buffer -> ("regions" ::: Vector BufferImageCopy) -> io () cmdCopyImageToBuffer CommandBuffer commandBuffer "srcImage" ::: Image srcImage "srcImageLayout" ::: ImageLayout srcImageLayout Buffer dstBuffer "regions" ::: Vector BufferImageCopy regions = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferImageCopy) -> IO ()) vkCmdCopyImageToBufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdCopyImageToBuffer is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @BufferImageCopy ((forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector BufferImageCopy regions)) forall a. Num a => a -> a -> a * Int 56) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i BufferImageCopy e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRegions" ::: Ptr BufferImageCopy pPRegions forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 56 forall a. Num a => a -> a -> a * (Int i)) :: Ptr BufferImageCopy) (BufferImageCopy e)) ("regions" ::: Vector BufferImageCopy regions) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdCopyImageToBuffer" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector BufferImageCopy regions)) :: Word32)) ("pRegions" ::: Ptr BufferImageCopy pPRegions)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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 a “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 -- -- - #VUID-vkCmdUpdateBuffer-dstOffset-00032# @dstOffset@ /must/ be less -- than the size of @dstBuffer@ -- -- - #VUID-vkCmdUpdateBuffer-dataSize-00033# @dataSize@ /must/ be less -- than or equal to the size of @dstBuffer@ minus @dstOffset@ -- -- - #VUID-vkCmdUpdateBuffer-dstBuffer-00034# @dstBuffer@ /must/ have -- been created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdUpdateBuffer-dstBuffer-00035# If @dstBuffer@ is -- non-sparse then it /must/ be bound completely and contiguously to a -- single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdUpdateBuffer-dstOffset-00036# @dstOffset@ /must/ be a -- multiple of @4@ -- -- - #VUID-vkCmdUpdateBuffer-dataSize-00037# @dataSize@ /must/ be less -- than or equal to @65536@ -- -- - #VUID-vkCmdUpdateBuffer-dataSize-00038# @dataSize@ /must/ be a -- multiple of @4@ -- -- - #VUID-vkCmdUpdateBuffer-commandBuffer-01813# If @commandBuffer@ is -- an unprotected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be a protected buffer -- -- - #VUID-vkCmdUpdateBuffer-commandBuffer-01814# If @commandBuffer@ is a -- protected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be an unprotected buffer -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdUpdateBuffer-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdUpdateBuffer-dstBuffer-parameter# @dstBuffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdUpdateBuffer-pData-parameter# @pData@ /must/ be a valid -- pointer to an array of @dataSize@ bytes -- -- - #VUID-vkCmdUpdateBuffer-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdUpdateBuffer-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - #VUID-vkCmdUpdateBuffer-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdUpdateBuffer-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdUpdateBuffer-dataSize-arraylength# @dataSize@ /must/ be -- greater than @0@ -- -- - #VUID-vkCmdUpdateBuffer-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> ("data" ::: Ptr ()) -> io () cmdUpdateBuffer CommandBuffer commandBuffer Buffer dstBuffer "offset" ::: DeviceSize dstOffset "offset" ::: DeviceSize dataSize "data" ::: Ptr () data' = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> ("data" ::: Ptr ()) -> IO ()) vkCmdUpdateBufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdUpdateBuffer is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdUpdateBuffer" (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')) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 a “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 -- -- - #VUID-vkCmdFillBuffer-dstOffset-00024# @dstOffset@ /must/ be less -- than the size of @dstBuffer@ -- -- - #VUID-vkCmdFillBuffer-dstOffset-00025# @dstOffset@ /must/ be a -- multiple of @4@ -- -- - #VUID-vkCmdFillBuffer-size-00026# If @size@ is not equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ be greater -- than @0@ -- -- - #VUID-vkCmdFillBuffer-size-00027# 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@ -- -- - #VUID-vkCmdFillBuffer-size-00028# If @size@ is not equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ be a multiple -- of @4@ -- -- - #VUID-vkCmdFillBuffer-dstBuffer-00029# @dstBuffer@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdFillBuffer-apiVersion-07894# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_maintenance1 VK_KHR_maintenance1> -- extension is not enabled and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties'::@apiVersion@ -- is less than Vulkan 1.1, the 'Vulkan.Core10.Handles.CommandPool' -- that @commandBuffer@ was allocated from /must/ support graphics or -- compute operations -- -- - #VUID-vkCmdFillBuffer-dstBuffer-00031# If @dstBuffer@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdFillBuffer-commandBuffer-01811# If @commandBuffer@ is an -- unprotected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be a protected buffer -- -- - #VUID-vkCmdFillBuffer-commandBuffer-01812# If @commandBuffer@ is a -- protected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstBuffer@ /must/ not be an unprotected buffer -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdFillBuffer-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdFillBuffer-dstBuffer-parameter# @dstBuffer@ /must/ be a -- valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdFillBuffer-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdFillBuffer-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics or compute -- operations -- -- - #VUID-vkCmdFillBuffer-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdFillBuffer-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdFillBuffer-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> io () cmdFillBuffer CommandBuffer commandBuffer Buffer dstBuffer "offset" ::: DeviceSize dstOffset "offset" ::: DeviceSize size "firstViewport" ::: Word32 data' = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdFillBufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdFillBuffer is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdFillBuffer" (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')) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdClearColorImage-image-01993# The -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-format-features format features> -- of @image@ /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT' -- -- - #VUID-vkCmdClearColorImage-image-00002# @image@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdClearColorImage-image-01545# @image@ /must/ not use any -- of the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion formats that require a sampler Y′CBCR conversion> -- -- - #VUID-vkCmdClearColorImage-image-00003# If @image@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdClearColorImage-imageLayout-00004# @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' -- -- - #VUID-vkCmdClearColorImage-imageLayout-01394# @imageLayout@ /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' -- -- - #VUID-vkCmdClearColorImage-aspectMask-02498# 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' -- -- - #VUID-vkCmdClearColorImage-baseMipLevel-01470# 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 -- -- - #VUID-vkCmdClearColorImage-pRanges-01692# 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 or equal to the -- @mipLevels@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' when -- @image@ was created -- -- - #VUID-vkCmdClearColorImage-baseArrayLayer-01472# 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 -- -- - #VUID-vkCmdClearColorImage-pRanges-01693# 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 or equal to the -- @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' -- when @image@ was created -- -- - #VUID-vkCmdClearColorImage-image-00007# @image@ /must/ not have a -- compressed or depth\/stencil format -- -- - #VUID-vkCmdClearColorImage-pColor-04961# @pColor@ /must/ be a valid -- pointer to a 'ClearColorValue' union -- -- - #VUID-vkCmdClearColorImage-commandBuffer-01805# If @commandBuffer@ -- is an unprotected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @image@ /must/ not be a protected image -- -- - #VUID-vkCmdClearColorImage-commandBuffer-01806# If @commandBuffer@ -- is a protected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, /must/ not be an unprotected image -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdClearColorImage-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdClearColorImage-image-parameter# @image@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdClearColorImage-imageLayout-parameter# @imageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdClearColorImage-pRanges-parameter# @pRanges@ /must/ be a -- valid pointer to an array of @rangeCount@ valid -- 'Vulkan.Core10.ImageView.ImageSubresourceRange' structures -- -- - #VUID-vkCmdClearColorImage-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdClearColorImage-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - #VUID-vkCmdClearColorImage-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdClearColorImage-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdClearColorImage-rangeCount-arraylength# @rangeCount@ -- /must/ be greater than @0@ -- -- - #VUID-vkCmdClearColorImage-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | Secondary | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views Image Views>. ("ranges" ::: Vector ImageSubresourceRange) -> io () cmdClearColorImage :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ClearColorValue -> ("ranges" ::: Vector ImageSubresourceRange) -> io () cmdClearColorImage CommandBuffer commandBuffer "srcImage" ::: Image image "srcImageLayout" ::: ImageLayout imageLayout ClearColorValue color "ranges" ::: Vector ImageSubresourceRange ranges = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("pColor" ::: Ptr ClearColorValue) -> ("firstViewport" ::: Word32) -> ("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) vkCmdClearColorImagePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdClearColorImage is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (ClearColorValue color) "pRanges" ::: Ptr ImageSubresourceRange pPRanges <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ImageSubresourceRange ((forall a. Vector a -> Int Data.Vector.length ("ranges" ::: Vector ImageSubresourceRange ranges)) forall a. Num a => a -> a -> a * Int 20) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ImageSubresourceRange e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRanges" ::: Ptr ImageSubresourceRange pPRanges forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 20 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageSubresourceRange) (ImageSubresourceRange e)) ("ranges" ::: Vector ImageSubresourceRange ranges) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdClearColorImage" (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 ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("ranges" ::: Vector ImageSubresourceRange ranges)) :: Word32)) ("pRanges" ::: Ptr ImageSubresourceRange pPRanges)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdClearDepthStencilImage-image-01994# The -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-format-features format features> -- of @image@ /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT' -- -- - #VUID-vkCmdClearDepthStencilImage-pRanges-02658# 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@ -- -- - #VUID-vkCmdClearDepthStencilImage-pRanges-02659# 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@ -- -- - #VUID-vkCmdClearDepthStencilImage-pRanges-02660# 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@ -- -- - #VUID-vkCmdClearDepthStencilImage-image-00010# If @image@ is -- non-sparse then it /must/ be bound completely and contiguously to a -- single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdClearDepthStencilImage-imageLayout-00011# @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' -- -- - #VUID-vkCmdClearDepthStencilImage-imageLayout-00012# @imageLayout@ -- /must/ be either of -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL' -- or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL' -- -- - #VUID-vkCmdClearDepthStencilImage-aspectMask-02824# 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' -- -- - #VUID-vkCmdClearDepthStencilImage-image-02825# 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 -- -- - #VUID-vkCmdClearDepthStencilImage-image-02826# 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 -- -- - #VUID-vkCmdClearDepthStencilImage-baseMipLevel-01474# 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 -- -- - #VUID-vkCmdClearDepthStencilImage-pRanges-01694# 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 or equal to the -- @mipLevels@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' when -- @image@ was created -- -- - #VUID-vkCmdClearDepthStencilImage-baseArrayLayer-01476# 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 -- -- - #VUID-vkCmdClearDepthStencilImage-pRanges-01695# 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 or equal to the -- @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' -- when @image@ was created -- -- - #VUID-vkCmdClearDepthStencilImage-image-00014# @image@ /must/ have a -- depth\/stencil format -- -- - #VUID-vkCmdClearDepthStencilImage-commandBuffer-01807# If -- @commandBuffer@ is an unprotected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @image@ /must/ not be a protected image -- -- - #VUID-vkCmdClearDepthStencilImage-commandBuffer-01808# If -- @commandBuffer@ is a protected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @image@ /must/ not be an unprotected image -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdClearDepthStencilImage-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdClearDepthStencilImage-image-parameter# @image@ /must/ be -- a valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdClearDepthStencilImage-imageLayout-parameter# -- @imageLayout@ /must/ be a valid -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value -- -- - #VUID-vkCmdClearDepthStencilImage-pDepthStencil-parameter# -- @pDepthStencil@ /must/ be a valid pointer to a valid -- 'ClearDepthStencilValue' structure -- -- - #VUID-vkCmdClearDepthStencilImage-pRanges-parameter# @pRanges@ -- /must/ be a valid pointer to an array of @rangeCount@ valid -- 'Vulkan.Core10.ImageView.ImageSubresourceRange' structures -- -- - #VUID-vkCmdClearDepthStencilImage-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdClearDepthStencilImage-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdClearDepthStencilImage-renderpass# This command /must/ -- only be called outside of a render pass instance -- -- - #VUID-vkCmdClearDepthStencilImage-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- - #VUID-vkCmdClearDepthStencilImage-rangeCount-arraylength# -- @rangeCount@ /must/ be greater than @0@ -- -- - #VUID-vkCmdClearDepthStencilImage-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views Image Views>. ("ranges" ::: Vector ImageSubresourceRange) -> io () cmdClearDepthStencilImage :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ClearDepthStencilValue -> ("ranges" ::: Vector ImageSubresourceRange) -> io () cmdClearDepthStencilImage CommandBuffer commandBuffer "srcImage" ::: Image image "srcImageLayout" ::: ImageLayout imageLayout ClearDepthStencilValue depthStencil "ranges" ::: Vector ImageSubresourceRange ranges = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> ("firstViewport" ::: Word32) -> ("pRanges" ::: Ptr ImageSubresourceRange) -> IO ()) vkCmdClearDepthStencilImagePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdClearDepthStencilImage is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (ClearDepthStencilValue depthStencil) "pRanges" ::: Ptr ImageSubresourceRange pPRanges <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ImageSubresourceRange ((forall a. Vector a -> Int Data.Vector.length ("ranges" ::: Vector ImageSubresourceRange ranges)) forall a. Num a => a -> a -> a * Int 20) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ImageSubresourceRange e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRanges" ::: Ptr ImageSubresourceRange pPRanges forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 20 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageSubresourceRange) (ImageSubresourceRange e)) ("ranges" ::: Vector ImageSubresourceRange ranges) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdClearDepthStencilImage" (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 ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("ranges" ::: Vector ImageSubresourceRange ranges)) :: Word32)) ("pRanges" ::: Ptr ImageSubresourceRange pPRanges)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- If the render pass has a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-fragmentdensitymapattachment fragment density map attachment>, -- clears follow the -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#clears clear commands>, -- 'cmdClearAttachments' is not a transfer command. It performs its -- operations in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-order rasterization order>. -- For color attachments, the operations are executed as color attachment -- writes, by the -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT' -- stage. For depth\/stencil attachments, the operations are executed as -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fragops-depth depth writes> -- and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fragops-stencil 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. -- -- 'cmdClearAttachments' is not affected by the bound pipeline state. -- -- Note -- -- It is generally preferable to clear attachments by using the -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' load -- operation at the start of rendering, as it is more efficient on some -- implementations. -- -- If any attachment’s @aspectMask@ to be cleared is not backed by an image -- view, the clear has no effect on that aspect. -- -- If an attachment being cleared refers to an image view created with an -- @aspectMask@ equal to one of -- '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', it -- is considered to be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' for -- purposes of this command, and /must/ be cleared with the -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' aspect -- as specified by -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#image-views-plane-promotion image view creation>. -- -- == Valid Usage -- -- - #VUID-vkCmdClearAttachments-aspectMask-07884# If the current render -- pass instance does not use dynamic rendering, and the @aspectMask@ -- member of any element of @pAttachments@ contains -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT', -- the current subpass instance’s depth-stencil attachment /must/ be -- either 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' or the -- attachment @format@ /must/ contain a depth component -- -- - #VUID-vkCmdClearAttachments-aspectMask-07885# If the current render -- pass instance does not use dynamic rendering, and the @aspectMask@ -- member of any element of @pAttachments@ contains -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', -- the current subpass instance’s depth-stencil attachment /must/ be -- either 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' or the -- attachment @format@ /must/ contain a stencil component -- -- - #VUID-vkCmdClearAttachments-aspectMask-07271# If the @aspectMask@ -- member of any element of @pAttachments@ contains -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', -- the @colorAttachment@ /must/ be a valid color attachment index in -- the current render pass instance -- -- - #VUID-vkCmdClearAttachments-rect-02682# The @rect@ member of each -- element of @pRects@ /must/ have an @extent.width@ greater than @0@ -- -- - #VUID-vkCmdClearAttachments-rect-02683# The @rect@ member of each -- element of @pRects@ /must/ have an @extent.height@ greater than @0@ -- -- - #VUID-vkCmdClearAttachments-pRects-00016# The rectangular region -- specified by each element of @pRects@ /must/ be contained within the -- render area of the current render pass instance -- -- - #VUID-vkCmdClearAttachments-pRects-06937# The layers specified by -- each element of @pRects@ /must/ be contained within every attachment -- that @pAttachments@ refers to, i.e. for each element of @pRects@, -- 'ClearRect'::@baseArrayLayer@ + 'ClearRect'::@layerCount@ /must/ be -- less than or equal to the number of layers rendered to in the -- current render pass instance -- -- - #VUID-vkCmdClearAttachments-layerCount-01934# The @layerCount@ -- member of each element of @pRects@ /must/ not be @0@ -- -- - #VUID-vkCmdClearAttachments-commandBuffer-02504# If @commandBuffer@ -- is an unprotected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, each attachment to be cleared /must/ not be a -- protected image -- -- - #VUID-vkCmdClearAttachments-commandBuffer-02505# If @commandBuffer@ -- is a protected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, each attachment to be cleared /must/ not be an -- unprotected image -- -- - #VUID-vkCmdClearAttachments-baseArrayLayer-00018# If the render pass -- instance this is recorded in uses multiview, then @baseArrayLayer@ -- /must/ be zero and @layerCount@ /must/ be one -- -- - #VUID-vkCmdClearAttachments-aspectMask-09298# If the subpass this is -- recorded in performs an external format resolve, the @aspectMask@ -- member of any element of @pAttachments@ /must/ not include -- @VK_IMAGE_ASPECT_PLANE_i_BIT@ for any index /i/ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdClearAttachments-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdClearAttachments-pAttachments-parameter# @pAttachments@ -- /must/ be a valid pointer to an array of @attachmentCount@ valid -- 'ClearAttachment' structures -- -- - #VUID-vkCmdClearAttachments-pRects-parameter# @pRects@ /must/ be a -- valid pointer to an array of @rectCount@ 'ClearRect' structures -- -- - #VUID-vkCmdClearAttachments-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdClearAttachments-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdClearAttachments-renderpass# This command /must/ only be -- called inside of a render pass instance -- -- - #VUID-vkCmdClearAttachments-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdClearAttachments-attachmentCount-arraylength# -- @attachmentCount@ /must/ be greater than @0@ -- -- - #VUID-vkCmdClearAttachments-rectCount-arraylength# @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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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. ("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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("attachments" ::: Vector ClearAttachment) -> ("rects" ::: Vector ClearRect) -> io () cmdClearAttachments CommandBuffer commandBuffer "attachments" ::: Vector ClearAttachment attachments "rects" ::: Vector ClearRect rects = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("pAttachments" ::: Ptr ClearAttachment) -> ("firstViewport" ::: Word32) -> ("pRects" ::: Ptr ClearRect) -> IO ()) vkCmdClearAttachmentsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdClearAttachments is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ClearAttachment ((forall a. Vector a -> Int Data.Vector.length ("attachments" ::: Vector ClearAttachment attachments)) forall a. Num a => a -> a -> a * Int 24) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ClearAttachment e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct ("pAttachments" ::: Ptr ClearAttachment pPAttachments forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ClearAttachment) (ClearAttachment e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) ("attachments" ::: Vector ClearAttachment attachments) "pRects" ::: Ptr ClearRect pPRects <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ClearRect ((forall a. Vector a -> Int Data.Vector.length ("rects" ::: Vector ClearRect rects)) forall a. Num a => a -> a -> a * Int 24) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ClearRect e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRects" ::: Ptr ClearRect pPRects forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ClearRect) (ClearRect e)) ("rects" ::: Vector ClearRect rects) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdClearAttachments" (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("pAttachments" ::: Ptr ClearAttachment) -> ("firstViewport" ::: Word32) -> ("pRects" ::: Ptr ClearRect) -> IO () vkCmdClearAttachments' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("attachments" ::: Vector ClearAttachment attachments)) :: Word32)) ("pAttachments" ::: Ptr ClearAttachment pPAttachments) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("rects" ::: Vector ClearRect rects)) :: Word32)) ("pRects" ::: Ptr ClearRect pPRects)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdResolveImage-commandBuffer-01837# If @commandBuffer@ is -- an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @srcImage@ /must/ not be a protected image -- -- - #VUID-vkCmdResolveImage-commandBuffer-01838# If @commandBuffer@ is -- an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be a protected image -- -- - #VUID-vkCmdResolveImage-commandBuffer-01839# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, @dstImage@ /must/ not be an unprotected image -- -- - #VUID-vkCmdResolveImage-pRegions-00255# The union of all source -- regions, and the union of all destination regions, specified by the -- elements of @pRegions@, /must/ not overlap in memory -- -- - #VUID-vkCmdResolveImage-srcImage-00256# If @srcImage@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdResolveImage-srcImage-00257# @srcImage@ /must/ have a -- sample count equal to any valid sample count value other than -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdResolveImage-dstImage-00258# If @dstImage@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdResolveImage-dstImage-00259# @dstImage@ /must/ have a -- sample count equal to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdResolveImage-srcImageLayout-00260# @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' -- -- - #VUID-vkCmdResolveImage-srcImageLayout-01400# @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' -- -- - #VUID-vkCmdResolveImage-dstImageLayout-00262# @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' -- -- - #VUID-vkCmdResolveImage-dstImageLayout-01401# @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' -- -- - #VUID-vkCmdResolveImage-dstImage-02003# 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' -- -- - #VUID-vkCmdResolveImage-linearColorAttachment-06519# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-linearColorAttachment linearColorAttachment> -- feature is enabled and the image is created with -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR', 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.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_LINEAR_COLOR_ATTACHMENT_BIT_NV' -- -- - #VUID-vkCmdResolveImage-srcImage-01386# @srcImage@ and @dstImage@ -- /must/ have been created with the same image format -- -- - #VUID-vkCmdResolveImage-srcSubresource-01709# 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 -- -- - #VUID-vkCmdResolveImage-dstSubresource-01710# 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 -- -- - #VUID-vkCmdResolveImage-srcSubresource-01711# The -- @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of -- each element of @pRegions@ , if @srcSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ -- was created -- -- - #VUID-vkCmdResolveImage-dstSubresource-01712# The -- @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of -- each element of @pRegions@ , if @dstSubresource.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- is not enabled, /must/ be less than or equal to the @arrayLayers@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ -- was created -- -- - #VUID-vkCmdResolveImage-dstImage-02546# @dstImage@ and @srcImage@ -- /must/ not have been created with @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - #VUID-vkCmdResolveImage-srcImage-04446# If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element -- of @pRegions@, @srcSubresource.layerCount@ /must/ be @1@ -- -- - #VUID-vkCmdResolveImage-srcImage-04447# If @dstImage@ is 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@ -- -- - #VUID-vkCmdResolveImage-srcOffset-00269# 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@ -- -- - #VUID-vkCmdResolveImage-srcOffset-00270# 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@ -- -- - #VUID-vkCmdResolveImage-srcImage-00271# 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@ -- -- - #VUID-vkCmdResolveImage-srcOffset-00272# 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@ -- -- - #VUID-vkCmdResolveImage-srcImage-00273# 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@ -- -- - #VUID-vkCmdResolveImage-dstOffset-00274# 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@ -- -- - #VUID-vkCmdResolveImage-dstOffset-00275# 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@ -- -- - #VUID-vkCmdResolveImage-dstImage-00276# 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@ -- -- - #VUID-vkCmdResolveImage-dstOffset-00277# 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@ -- -- - #VUID-vkCmdResolveImage-dstImage-00278# 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@ -- -- - #VUID-vkCmdResolveImage-srcImage-06762# @srcImage@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - #VUID-vkCmdResolveImage-srcImage-06763# 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' -- -- - #VUID-vkCmdResolveImage-dstImage-06764# @dstImage@ /must/ have been -- created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdResolveImage-dstImage-06765# 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' -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdResolveImage-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdResolveImage-srcImage-parameter# @srcImage@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdResolveImage-srcImageLayout-parameter# @srcImageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdResolveImage-dstImage-parameter# @dstImage@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-vkCmdResolveImage-dstImageLayout-parameter# @dstImageLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- - #VUID-vkCmdResolveImage-pRegions-parameter# @pRegions@ /must/ be a -- valid pointer to an array of @regionCount@ valid 'ImageResolve' -- structures -- -- - #VUID-vkCmdResolveImage-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdResolveImage-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdResolveImage-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdResolveImage-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdResolveImage-regionCount-arraylength# @regionCount@ -- /must/ be greater than @0@ -- -- - #VUID-vkCmdResolveImage-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("regions" ::: Vector ImageResolve) -> io () cmdResolveImage CommandBuffer commandBuffer "srcImage" ::: Image srcImage "srcImageLayout" ::: ImageLayout srcImageLayout "srcImage" ::: Image dstImage "srcImageLayout" ::: ImageLayout dstImageLayout "regions" ::: Vector ImageResolve regions = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("srcImage" ::: Image) -> ("srcImageLayout" ::: ImageLayout) -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr ImageResolve) -> IO ()) vkCmdResolveImagePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdResolveImage is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ImageResolve ((forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector ImageResolve regions)) forall a. Num a => a -> a -> a * Int 68) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ImageResolve e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pRegions" ::: Ptr ImageResolve pPRegions forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 68 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageResolve) (ImageResolve e)) ("regions" ::: Vector ImageResolve regions) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdResolveImage" (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) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector ImageResolve regions)) :: Word32)) ("pRegions" ::: Ptr ImageResolve pPRegions)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetEvent :: FunPtr (Ptr CommandBuffer_T -> Event -> PipelineStageFlags -> IO ()) -> Ptr CommandBuffer_T -> Event -> PipelineStageFlags -> IO () -- | vkCmdSetEvent - Set an event object to signaled state -- -- = Description -- -- 'cmdSetEvent' behaves identically to -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdSetEvent2', -- except that it does not define an access scope, and /must/ only be used -- with 'cmdWaitEvents', not -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWaitEvents2'. -- -- == Valid Usage -- -- - #VUID-vkCmdSetEvent-stageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdSetEvent-stageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdSetEvent-stageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdSetEvent-stageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdSetEvent-stageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdSetEvent-stageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdSetEvent-stageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdSetEvent-stageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdSetEvent-stageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @stageMask@ /must/ not be @0@ -- -- - #VUID-vkCmdSetEvent-stageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdSetEvent-stageMask-06457# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages> -- -- - #VUID-vkCmdSetEvent-stageMask-01149# @stageMask@ /must/ not include -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT' -- -- - #VUID-vkCmdSetEvent-commandBuffer-01152# The current device mask of -- @commandBuffer@ /must/ include exactly one physical device -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetEvent-commandBuffer-parameter# @commandBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetEvent-event-parameter# @event@ /must/ be a valid -- 'Vulkan.Core10.Handles.Event' handle -- -- - #VUID-vkCmdSetEvent-stageMask-parameter# @stageMask@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-vkCmdSetEvent-commandBuffer-recording# @commandBuffer@ /must/ -- be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetEvent-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, decode, or encode -- operations -- -- - #VUID-vkCmdSetEvent-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdSetEvent-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Both | Graphics | Synchronization | -- | Secondary | | | Compute | | -- | | | | Decode | | -- | | | | Encode | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask> -- used to determine the first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope>. ("stageMask" ::: PipelineStageFlags) -> io () cmdSetEvent :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Event -> ("stageMask" ::: PipelineStageFlags) -> io () cmdSetEvent CommandBuffer commandBuffer Event event "stageMask" ::: PipelineStageFlags stageMask = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ()) vkCmdSetEventPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetEvent is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetEvent" (Ptr CommandBuffer_T -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO () vkCmdSetEvent' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Event event) ("stageMask" ::: PipelineStageFlags stageMask)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdResetEvent :: FunPtr (Ptr CommandBuffer_T -> Event -> PipelineStageFlags -> IO ()) -> Ptr CommandBuffer_T -> Event -> PipelineStageFlags -> IO () -- | vkCmdResetEvent - Reset an event object to non-signaled state -- -- = Description -- -- 'cmdResetEvent' behaves identically to -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdResetEvent2'. -- -- == Valid Usage -- -- - #VUID-vkCmdResetEvent-stageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdResetEvent-stageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdResetEvent-stageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdResetEvent-stageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdResetEvent-stageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdResetEvent-stageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdResetEvent-stageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdResetEvent-stageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdResetEvent-stageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @stageMask@ /must/ not be @0@ -- -- - #VUID-vkCmdResetEvent-stageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @stageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdResetEvent-stageMask-06458# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages> -- -- - #VUID-vkCmdResetEvent-stageMask-01153# @stageMask@ /must/ not -- include -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT' -- -- - #VUID-vkCmdResetEvent-event-03834# There /must/ be an execution -- dependency between 'cmdResetEvent' and the execution of any -- 'cmdWaitEvents' that includes @event@ in its @pEvents@ parameter -- -- - #VUID-vkCmdResetEvent-event-03835# There /must/ be an execution -- dependency between 'cmdResetEvent' and the execution of any -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWaitEvents2' -- that includes @event@ in its @pEvents@ parameter -- -- - #VUID-vkCmdResetEvent-commandBuffer-01157# @commandBuffer@’s current -- device mask /must/ include exactly one physical device -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdResetEvent-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdResetEvent-event-parameter# @event@ /must/ be a valid -- 'Vulkan.Core10.Handles.Event' handle -- -- - #VUID-vkCmdResetEvent-stageMask-parameter# @stageMask@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-vkCmdResetEvent-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdResetEvent-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, decode, or encode -- operations -- -- - #VUID-vkCmdResetEvent-renderpass# This command /must/ only be called -- outside of a render pass instance -- -- - #VUID-vkCmdResetEvent-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Both | Graphics | Synchronization | -- | Secondary | | | Compute | | -- | | | | Decode | | -- | | | | Encode | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages source stage mask> -- used to determine when the @event@ is unsignaled. ("stageMask" ::: PipelineStageFlags) -> io () cmdResetEvent :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Event -> ("stageMask" ::: PipelineStageFlags) -> io () cmdResetEvent CommandBuffer commandBuffer Event event "stageMask" ::: PipelineStageFlags stageMask = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO ()) vkCmdResetEventPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdResetEvent is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdResetEvent" (Ptr CommandBuffer_T -> Event -> ("stageMask" ::: PipelineStageFlags) -> IO () vkCmdResetEvent' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Event event) ("stageMask" ::: PipelineStageFlags stageMask)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdWaitEventsUnsafe :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr (SomeStruct BufferMemoryBarrier) -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr (SomeStruct BufferMemoryBarrier) -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () -- | cmdWaitEvents with selectable safeness cmdWaitEventsSafeOrUnsafe :: forall io . (MonadIO io) => (FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr (SomeStruct BufferMemoryBarrier) -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Event -> PipelineStageFlags -> PipelineStageFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr (SomeStruct 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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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 (SomeStruct BufferMemoryBarrier)) -> -- | @pImageMemoryBarriers@ is a pointer to an array of -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures. ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdWaitEventsSafeOrUnsafe :: forall (io :: * -> *). MonadIO io => (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> Ptr Event -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> CommandBuffer -> ("events" ::: Vector Event) -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("memoryBarriers" ::: Vector MemoryBarrier) -> ("bufferMemoryBarriers" ::: Vector (SomeStruct 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 (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () mkVkCmdWaitEvents CommandBuffer commandBuffer "events" ::: Vector Event events "stageMask" ::: PipelineStageFlags srcStageMask "stageMask" ::: PipelineStageFlags dstStageMask "memoryBarriers" ::: Vector MemoryBarrier memoryBarriers "bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers "imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCmdWaitEventsPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> Ptr Event -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) pVkCmdWaitEvents (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> Ptr Event -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) vkCmdWaitEventsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdWaitEvents is null" forall a. Maybe a Nothing 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 (SomeStruct 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 (SomeStruct 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 (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) vkCmdWaitEventsPtr Ptr Event pPEvents <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Event ((forall a. Vector a -> Int Data.Vector.length ("events" ::: Vector Event events)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Event e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Event pPEvents forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Event) (Event e)) ("events" ::: Vector Event events) Ptr MemoryBarrier pPMemoryBarriers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @MemoryBarrier ((forall a. Vector a -> Int Data.Vector.length ("memoryBarriers" ::: Vector MemoryBarrier memoryBarriers)) forall a. Num a => a -> a -> a * Int 24) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i MemoryBarrier e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr MemoryBarrier pPMemoryBarriers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr MemoryBarrier) (MemoryBarrier e)) ("memoryBarriers" ::: Vector MemoryBarrier memoryBarriers) Ptr (BufferMemoryBarrier Any) pPBufferMemoryBarriers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @(BufferMemoryBarrier _) ((forall a. Vector a -> Int Data.Vector.length ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers)) forall a. Num a => a -> a -> a * Int 56) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i SomeStruct BufferMemoryBarrier e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (a :: [*] -> *) b. (forall (es :: [*]). (Extendss a es, PokeChain es) => ToCStruct (a es)) => Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b pokeSomeCStruct (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (BufferMemoryBarrier Any) pPBufferMemoryBarriers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 56 forall a. Num a => a -> a -> a * (Int i)) :: Ptr (BufferMemoryBarrier _))) (SomeStruct BufferMemoryBarrier e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers) Ptr (ImageMemoryBarrier Any) pPImageMemoryBarriers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @(ImageMemoryBarrier _) ((forall a. Vector a -> Int Data.Vector.length ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers)) forall a. Num a => a -> a -> a * Int 72) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i SomeStruct ImageMemoryBarrier e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (a :: [*] -> *) b. (forall (es :: [*]). (Extendss a es, PokeChain es) => ToCStruct (a es)) => Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b pokeSomeCStruct (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (ImageMemoryBarrier Any) pPImageMemoryBarriers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 72 forall a. Num a => a -> a -> a * (Int i)) :: Ptr (ImageMemoryBarrier _))) (SomeStruct ImageMemoryBarrier e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdWaitEvents" (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> Ptr Event -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () vkCmdWaitEvents' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("events" ::: Vector Event events)) :: Word32)) (Ptr Event pPEvents) ("stageMask" ::: PipelineStageFlags srcStageMask) ("stageMask" ::: PipelineStageFlags dstStageMask) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("memoryBarriers" ::: Vector MemoryBarrier memoryBarriers)) :: Word32)) (Ptr MemoryBarrier pPMemoryBarriers) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers)) :: Word32)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (BufferMemoryBarrier Any) pPBufferMemoryBarriers)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers)) :: Word32)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (ImageMemoryBarrier Any) pPImageMemoryBarriers))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () -- | vkCmdWaitEvents - Wait for one or more events and insert a set of memory -- -- = Description -- -- 'cmdWaitEvents' is largely similar to -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWaitEvents2', -- but /can/ only wait on signal operations defined by 'cmdSetEvent'. As -- 'cmdSetEvent' does not define any access scopes, 'cmdWaitEvents' defines -- the first access scope for each event signal operation in addition to -- its own access scopes. -- -- Note -- -- Since 'cmdSetEvent' does not have any dependency information beyond a -- stage mask, implementations do not have the same opportunity to perform -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-available-and-visible availability and visibility operations> -- or -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-image-layout-transitions image layout transitions> -- in advance as they do with -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdSetEvent2' and -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWaitEvents2'. -- -- 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order> -- are included in the first synchronization scope, if the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically latest> -- pipeline stage in their @stageMask@ parameter is -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically earlier> -- than or equal to the -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands that occur later in -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask> -- specified by @dstStageMask@. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope> -- is limited to accesses in the pipeline stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope> -- is limited to accesses in the pipeline stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-memory-barriers memory barriers>. -- If no memory barriers are specified, then the second access scope -- includes no accesses. -- -- == Valid Usage -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @srcStageMask@ /must/ not be @0@ -- -- - #VUID-vkCmdWaitEvents-srcStageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdWaitEvents-srcAccessMask-06257# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayQuery rayQuery> -- feature is not enabled and a memory barrier @srcAccessMask@ includes -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_ACCELERATION_STRUCTURE_READ_BIT_KHR', -- @srcStageMask@ /must/ not include any of the -- @VK_PIPELINE_STAGE_*_SHADER_BIT@ stages except -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdWaitEvents-dstStageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @dstStageMask@ /must/ not be @0@ -- -- - #VUID-vkCmdWaitEvents-dstStageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdWaitEvents-dstAccessMask-06257# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayQuery rayQuery> -- feature is not enabled and a memory barrier @dstAccessMask@ includes -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_ACCELERATION_STRUCTURE_READ_BIT_KHR', -- @dstStageMask@ /must/ not include any of the -- @VK_PIPELINE_STAGE_*_SHADER_BIT@ stages except -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdWaitEvents-srcAccessMask-02815# 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> -- -- - #VUID-vkCmdWaitEvents-dstAccessMask-02816# 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> -- -- - #VUID-vkCmdWaitEvents-pBufferMemoryBarriers-02817# 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> -- -- - #VUID-vkCmdWaitEvents-pBufferMemoryBarriers-02818# 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> -- -- - #VUID-vkCmdWaitEvents-pImageMemoryBarriers-02819# 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> -- -- - #VUID-vkCmdWaitEvents-pImageMemoryBarriers-02820# 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> -- -- - #VUID-vkCmdWaitEvents-srcStageMask-06459# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages> -- -- - #VUID-vkCmdWaitEvents-dstStageMask-06460# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages> -- -- - #VUID-vkCmdWaitEvents-srcStageMask-01158# @srcStageMask@ /must/ be -- the bitwise OR of the @stageMask@ parameter used in previous calls -- to 'cmdSetEvent' with any of the elements of @pEvents@ and -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT' -- if any of the elements of @pEvents@ was set using -- 'Vulkan.Core10.Event.setEvent' -- -- - #VUID-vkCmdWaitEvents-srcStageMask-07308# If 'cmdWaitEvents' is -- being called inside a render pass instance, @srcStageMask@ /must/ -- not include -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT' -- -- - #VUID-vkCmdWaitEvents-srcQueueFamilyIndex-02803# The -- @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members of any -- element of @pBufferMemoryBarriers@ or @pImageMemoryBarriers@ /must/ -- be equal -- -- - #VUID-vkCmdWaitEvents-commandBuffer-01167# @commandBuffer@’s current -- device mask /must/ include exactly one physical device -- -- - #VUID-vkCmdWaitEvents-pEvents-03847# Elements of @pEvents@ /must/ -- not have been signaled by -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdSetEvent2' -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdWaitEvents-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdWaitEvents-pEvents-parameter# @pEvents@ /must/ be a valid -- pointer to an array of @eventCount@ valid -- 'Vulkan.Core10.Handles.Event' handles -- -- - #VUID-vkCmdWaitEvents-srcStageMask-parameter# @srcStageMask@ /must/ -- be a valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-vkCmdWaitEvents-dstStageMask-parameter# @dstStageMask@ /must/ -- be a valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-vkCmdWaitEvents-pMemoryBarriers-parameter# If -- @memoryBarrierCount@ is not @0@, @pMemoryBarriers@ /must/ be a valid -- pointer to an array of @memoryBarrierCount@ valid -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' structures -- -- - #VUID-vkCmdWaitEvents-pBufferMemoryBarriers-parameter# If -- @bufferMemoryBarrierCount@ is not @0@, @pBufferMemoryBarriers@ -- /must/ be a valid pointer to an array of @bufferMemoryBarrierCount@ -- valid 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures -- -- - #VUID-vkCmdWaitEvents-pImageMemoryBarriers-parameter# If -- @imageMemoryBarrierCount@ is not @0@, @pImageMemoryBarriers@ /must/ -- be a valid pointer to an array of @imageMemoryBarrierCount@ valid -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures -- -- - #VUID-vkCmdWaitEvents-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdWaitEvents-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, decode, or encode -- operations -- -- - #VUID-vkCmdWaitEvents-eventCount-arraylength# @eventCount@ /must/ be -- greater than @0@ -- -- - #VUID-vkCmdWaitEvents-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Both | Graphics | Synchronization | -- | Secondary | | | Compute | | -- | | | | Decode | | -- | | | | Encode | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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 (SomeStruct BufferMemoryBarrier)) -> -- | @pImageMemoryBarriers@ is a pointer to an array of -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures. ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdWaitEvents :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("events" ::: Vector Event) -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("memoryBarriers" ::: Vector MemoryBarrier) -> ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier)) -> ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdWaitEvents = forall (io :: * -> *). MonadIO io => (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> Ptr Event -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> CommandBuffer -> ("events" ::: Vector Event) -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("memoryBarriers" ::: Vector MemoryBarrier) -> ("bufferMemoryBarriers" ::: Vector (SomeStruct 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 (SomeStruct 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 (SomeStruct 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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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 (SomeStruct BufferMemoryBarrier)) -> -- | @pImageMemoryBarriers@ is a pointer to an array of -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures. ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdWaitEventsSafe :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("events" ::: Vector Event) -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("memoryBarriers" ::: Vector MemoryBarrier) -> ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier)) -> ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdWaitEventsSafe = forall (io :: * -> *). MonadIO io => (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> Ptr Event -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> CommandBuffer -> ("events" ::: Vector Event) -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> ("memoryBarriers" ::: Vector MemoryBarrier) -> ("bufferMemoryBarriers" ::: Vector (SomeStruct 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 (SomeStruct 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 (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> PipelineStageFlags -> PipelineStageFlags -> DependencyFlags -> Word32 -> Ptr MemoryBarrier -> Word32 -> Ptr (SomeStruct BufferMemoryBarrier) -> Word32 -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () -- | vkCmdPipelineBarrier - Insert a memory dependency -- -- = Description -- -- 'cmdPipelineBarrier' operates almost identically to -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdPipelineBarrier2', -- except that the scopes and barriers are defined as direct parameters -- rather than being defined by an -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.DependencyInfo'. -- -- When 'cmdPipelineBarrier' is submitted to a queue, it defines a memory -- dependency between commands that were submitted to the same queue before -- it, and those submitted to the same queue after it. -- -- If 'cmdPipelineBarrier' was recorded outside a render pass instance, the -- first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands that occur later in -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask> -- specified by @dstStageMask@. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope> -- is limited to accesses in the pipeline stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope> -- is limited to accesses in the pipeline stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space> -- pipeline stages is -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-local> -- - otherwise it is -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-global>. -- -- == Valid Usage -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @srcStageMask@ /must/ not be @0@ -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdPipelineBarrier-srcAccessMask-06257# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayQuery rayQuery> -- feature is not enabled and a memory barrier @srcAccessMask@ includes -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_ACCELERATION_STRUCTURE_READ_BIT_KHR', -- @srcStageMask@ /must/ not include any of the -- @VK_PIPELINE_STAGE_*_SHADER_BIT@ stages except -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @dstStageMask@ /must/ not be @0@ -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdPipelineBarrier-dstAccessMask-06257# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayQuery rayQuery> -- feature is not enabled and a memory barrier @dstAccessMask@ includes -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_ACCELERATION_STRUCTURE_READ_BIT_KHR', -- @dstStageMask@ /must/ not include any of the -- @VK_PIPELINE_STAGE_*_SHADER_BIT@ stages except -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdPipelineBarrier-srcAccessMask-02815# 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> -- -- - #VUID-vkCmdPipelineBarrier-dstAccessMask-02816# 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> -- -- - #VUID-vkCmdPipelineBarrier-pBufferMemoryBarriers-02817# 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> -- -- - #VUID-vkCmdPipelineBarrier-pBufferMemoryBarriers-02818# 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> -- -- - #VUID-vkCmdPipelineBarrier-pImageMemoryBarriers-02819# 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> -- -- - #VUID-vkCmdPipelineBarrier-pImageMemoryBarriers-02820# 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> -- -- - #VUID-vkCmdPipelineBarrier-None-07889# If 'cmdPipelineBarrier' is -- called within a render pass instance using a -- 'Vulkan.Core10.Handles.RenderPass' object, the render pass /must/ -- have been created with at least one subpass dependency that -- expresses a dependency from the current subpass to itself, does not -- include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT' if -- this command does not, does not include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT' -- if this command does not, and has -- <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 -- -- - #VUID-vkCmdPipelineBarrier-bufferMemoryBarrierCount-01178# If -- 'cmdPipelineBarrier' is called within a render pass instance using a -- 'Vulkan.Core10.Handles.RenderPass' object, it /must/ not include any -- buffer memory barriers -- -- - #VUID-vkCmdPipelineBarrier-image-04073# If 'cmdPipelineBarrier' is -- called within a render pass instance using a -- 'Vulkan.Core10.Handles.RenderPass' object, 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, color resolve, or depth\/stencil attachment -- -- - #VUID-vkCmdPipelineBarrier-image-09373# If 'cmdPipelineBarrier' is -- called within a render pass instance using a -- 'Vulkan.Core10.Handles.RenderPass' object, and the @image@ member of -- any image memory barrier is a color resolve attachment, the -- corresponding color attachment /must/ be -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' -- -- - #VUID-vkCmdPipelineBarrier-image-09374# If 'cmdPipelineBarrier' is -- called within a render pass instance using a -- 'Vulkan.Core10.Handles.RenderPass' object, and the @image@ member of -- any image memory barrier is a color resolve attachment, it /must/ -- have been created with a non-zero -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value -- -- - #VUID-vkCmdPipelineBarrier-oldLayout-01181# 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 -- -- - #VUID-vkCmdPipelineBarrier-srcQueueFamilyIndex-01182# If -- 'cmdPipelineBarrier' is called within a render pass instance, the -- @srcQueueFamilyIndex@ and @dstQueueFamilyIndex@ members of any -- memory barrier included in this command /must/ be equal -- -- - #VUID-vkCmdPipelineBarrier-None-07890# If 'cmdPipelineBarrier' is -- called within a render pass instance, and the source stage masks of -- any memory barriers include -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages>, -- destination stage masks of all memory barriers /must/ only include -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages> -- -- - #VUID-vkCmdPipelineBarrier-dependencyFlags-07891# If -- 'cmdPipelineBarrier' is called within a render pass instance, and -- and the source stage masks of any memory barriers include -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages>, -- then @dependencyFlags@ /must/ include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT' -- -- - #VUID-vkCmdPipelineBarrier-None-07892# If 'cmdPipelineBarrier' is -- called within a render pass instance, the source and destination -- stage masks of any memory barriers /must/ only include graphics -- pipeline stages -- -- - #VUID-vkCmdPipelineBarrier-dependencyFlags-01186# If -- 'cmdPipelineBarrier' is called outside of a render pass instance, -- the dependency flags /must/ not include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT' -- -- - #VUID-vkCmdPipelineBarrier-None-07893# If 'cmdPipelineBarrier' is -- called inside a render pass instance, and there is more than one -- view in the current subpass, dependency flags /must/ include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT' -- -- - #VUID-vkCmdPipelineBarrier-shaderTileImageColorReadAccess-08718# If -- 'cmdPipelineBarrier' is called within a render pass instance and -- none of the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderTileImageColorReadAccess shaderTileImageColorReadAccess>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderTileImageDepthReadAccess shaderTileImageDepthReadAccess>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderTileImageStencilReadAccess shaderTileImageStencilReadAccess> -- features are enabled, the render pass /must/ not have been started -- with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdPipelineBarrier-None-08719# If 'cmdPipelineBarrier' is -- called within a render pass instance started with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- it /must/ adhere to the restrictions in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-barriers-explicit-renderpass-tileimage Explicit Render Pass Tile Image Access Synchronization> -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-06461# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages> -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-06462# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages> -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdPipelineBarrier-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdPipelineBarrier-srcStageMask-parameter# @srcStageMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-vkCmdPipelineBarrier-dstStageMask-parameter# @dstStageMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-vkCmdPipelineBarrier-dependencyFlags-parameter# -- @dependencyFlags@ /must/ be a valid combination of -- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits' values -- -- - #VUID-vkCmdPipelineBarrier-pMemoryBarriers-parameter# If -- @memoryBarrierCount@ is not @0@, @pMemoryBarriers@ /must/ be a valid -- pointer to an array of @memoryBarrierCount@ valid -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' structures -- -- - #VUID-vkCmdPipelineBarrier-pBufferMemoryBarriers-parameter# If -- @bufferMemoryBarrierCount@ is not @0@, @pBufferMemoryBarriers@ -- /must/ be a valid pointer to an array of @bufferMemoryBarrierCount@ -- valid 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier' structures -- -- - #VUID-vkCmdPipelineBarrier-pImageMemoryBarriers-parameter# If -- @imageMemoryBarrierCount@ is not @0@, @pImageMemoryBarriers@ /must/ -- be a valid pointer to an array of @imageMemoryBarrierCount@ valid -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures -- -- - #VUID-vkCmdPipelineBarrier-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdPipelineBarrier-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, compute, decode, -- or encode 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Both | Transfer | Synchronization | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- | | | | Decode | | -- | | | | Encode | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stages>. ("srcStageMask" ::: PipelineStageFlags) -> -- | @dstStageMask@ is a bitmask of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- specifying the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stages>. ("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 (SomeStruct BufferMemoryBarrier)) -> -- | @pImageMemoryBarriers@ is a pointer to an array of -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' structures. ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdPipelineBarrier :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("memoryBarriers" ::: Vector MemoryBarrier) -> ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier)) -> ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier)) -> io () cmdPipelineBarrier CommandBuffer commandBuffer "stageMask" ::: PipelineStageFlags srcStageMask "stageMask" ::: PipelineStageFlags dstStageMask DependencyFlags dependencyFlags "memoryBarriers" ::: Vector MemoryBarrier memoryBarriers "bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers "imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCmdPipelineBarrierPtr :: FunPtr (Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct 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 (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) pVkCmdPipelineBarrier (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) vkCmdPipelineBarrierPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdPipelineBarrier is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdPipelineBarrier' :: Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () vkCmdPipelineBarrier' = FunPtr (Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) -> Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () mkVkCmdPipelineBarrier FunPtr (Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO ()) vkCmdPipelineBarrierPtr Ptr MemoryBarrier pPMemoryBarriers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @MemoryBarrier ((forall a. Vector a -> Int Data.Vector.length ("memoryBarriers" ::: Vector MemoryBarrier memoryBarriers)) forall a. Num a => a -> a -> a * Int 24) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i MemoryBarrier e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr MemoryBarrier pPMemoryBarriers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr MemoryBarrier) (MemoryBarrier e)) ("memoryBarriers" ::: Vector MemoryBarrier memoryBarriers) Ptr (BufferMemoryBarrier Any) pPBufferMemoryBarriers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @(BufferMemoryBarrier _) ((forall a. Vector a -> Int Data.Vector.length ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers)) forall a. Num a => a -> a -> a * Int 56) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i SomeStruct BufferMemoryBarrier e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (a :: [*] -> *) b. (forall (es :: [*]). (Extendss a es, PokeChain es) => ToCStruct (a es)) => Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b pokeSomeCStruct (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (BufferMemoryBarrier Any) pPBufferMemoryBarriers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 56 forall a. Num a => a -> a -> a * (Int i)) :: Ptr (BufferMemoryBarrier _))) (SomeStruct BufferMemoryBarrier e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers) Ptr (ImageMemoryBarrier Any) pPImageMemoryBarriers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @(ImageMemoryBarrier _) ((forall a. Vector a -> Int Data.Vector.length ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers)) forall a. Num a => a -> a -> a * Int 72) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i SomeStruct ImageMemoryBarrier e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (a :: [*] -> *) b. (forall (es :: [*]). (Extendss a es, PokeChain es) => ToCStruct (a es)) => Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b pokeSomeCStruct (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (ImageMemoryBarrier Any) pPImageMemoryBarriers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 72 forall a. Num a => a -> a -> a * (Int i)) :: Ptr (ImageMemoryBarrier _))) (SomeStruct ImageMemoryBarrier e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdPipelineBarrier" (Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> ("stageMask" ::: PipelineStageFlags) -> DependencyFlags -> ("firstViewport" ::: Word32) -> Ptr MemoryBarrier -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct BufferMemoryBarrier) -> ("firstViewport" ::: Word32) -> Ptr (SomeStruct ImageMemoryBarrier) -> IO () vkCmdPipelineBarrier' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("stageMask" ::: PipelineStageFlags srcStageMask) ("stageMask" ::: PipelineStageFlags dstStageMask) (DependencyFlags dependencyFlags) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("memoryBarriers" ::: Vector MemoryBarrier memoryBarriers)) :: Word32)) (Ptr MemoryBarrier pPMemoryBarriers) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("bufferMemoryBarriers" ::: Vector (SomeStruct BufferMemoryBarrier) bufferMemoryBarriers)) :: Word32)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (BufferMemoryBarrier Any) pPBufferMemoryBarriers)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("imageMemoryBarriers" ::: Vector (SomeStruct ImageMemoryBarrier) imageMemoryBarriers)) :: Word32)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions (Ptr (ImageMemoryBarrier Any) pPImageMemoryBarriers))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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://registry.khronos.org/vulkan/specs/1.3-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. -- -- Furthermore, if the query is started within a video coding scope, the -- following command buffer states are initialized for the query type: -- -- - #queries-operation-active-query-index# The /active_query_index/ is -- set to the value specified by @query@. -- -- - #queries-operation-last-activatable-query-index# The /last -- activatable query index/ is also set to the value specified by -- @query@. -- -- Each -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#video-coding video coding operation> -- stores a result to the query corresponding to the current active query -- index, followed by incrementing the active query index. If the active -- query index gets incremented past the last activatable query index, -- issuing any further video coding operations results in undefined -- behavior. -- -- Note -- -- In practice, this means that currently no more than a single video -- coding operation /must/ be issued between a begin and end query pair. -- -- This command defines an execution dependency between other query -- commands that reference the same query. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @query@ that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- -- The second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @query@ that occur later in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- -- The operation of this command happens after the first scope and happens -- before the second scope. -- -- == Valid Usage -- -- - #VUID-vkCmdBeginQuery-None-00807# All queries used by the command -- /must/ be /unavailable/ -- -- - #VUID-vkCmdBeginQuery-queryType-02804# The @queryType@ used to -- create @queryPool@ /must/ not be -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP' -- -- - #VUID-vkCmdBeginQuery-queryType-04728# The @queryType@ used to -- create @queryPool@ /must/ not be -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR' -- or -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR' -- -- - #VUID-vkCmdBeginQuery-queryType-06741# The @queryType@ used to -- create @queryPool@ /must/ not be -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SIZE_KHR' -- or -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_BOTTOM_LEVEL_POINTERS_KHR' -- -- - #VUID-vkCmdBeginQuery-queryType-04729# The @queryType@ used to -- create @queryPool@ /must/ not be -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV' -- -- - #VUID-vkCmdBeginQuery-queryType-00800# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-occlusionQueryPrecise occlusionQueryPrecise> -- 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' -- -- - #VUID-vkCmdBeginQuery-query-00802# @query@ /must/ be less than the -- number of queries in @queryPool@ -- -- - #VUID-vkCmdBeginQuery-queryType-00803# 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 -- -- - #VUID-vkCmdBeginQuery-queryType-00804# 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 -- -- - #VUID-vkCmdBeginQuery-queryType-00805# 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 -- -- - #VUID-vkCmdBeginQuery-commandBuffer-01885# @commandBuffer@ /must/ -- not be a protected command buffer -- -- - #VUID-vkCmdBeginQuery-query-00808# 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@ -- -- - #VUID-vkCmdBeginQuery-queryType-07126# If the @queryType@ used to -- create @queryPool@ was @VK_QUERY_TYPE_RESULT_STATUS_ONLY_KHR@, then -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ have been created with a queue family index -- that supports -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-result-status-only result status queries>, -- as indicated by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFamilyQueryResultStatusPropertiesKHR VkQueueFamilyQueryResultStatusPropertiesKHR>::@queryResultStatusSupport@ -- -- - #VUID-vkCmdBeginQuery-None-07127# If there is a bound video session, -- then there /must/ be no -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-operation-active active> -- queries -- -- - #VUID-vkCmdBeginQuery-queryType-07128# If the @queryType@ used to -- create @queryPool@ was @VK_QUERY_TYPE_RESULT_STATUS_ONLY_KHR@ and -- there is a bound video session, then @queryPool@ /must/ have been -- created with a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoProfileInfoKHR VkVideoProfileInfoKHR> -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.Query.QueryPoolCreateInfo' identical to the one -- specified in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoSessionCreateInfoKHR VkVideoSessionCreateInfoKHR>::@pVideoProfile@ -- the bound video session was created with -- -- - #VUID-vkCmdBeginQuery-queryType-04862# If the @queryType@ used to -- create @queryPool@ was @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@, -- then the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ -- was allocated from /must/ support -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#video-encode-operations video encode operations> -- -- - #VUID-vkCmdBeginQuery-queryType-07129# If the @queryType@ used to -- create @queryPool@ was @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@, -- then there /must/ be a bound video session -- -- - #VUID-vkCmdBeginQuery-queryType-07130# If the @queryType@ used to -- create @queryPool@ was @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@ and -- there is a bound video session, then @queryPool@ /must/ have been -- created with a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoProfileInfoKHR VkVideoProfileInfoKHR> -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.Query.QueryPoolCreateInfo' identical to the one -- specified in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoSessionCreateInfoKHR VkVideoSessionCreateInfoKHR>::@pVideoProfile@ -- the bound video session was created with -- -- - #VUID-vkCmdBeginQuery-queryType-07131# If the @queryType@ used to -- create @queryPool@ was not @VK_QUERY_TYPE_RESULT_STATUS_ONLY_KHR@ or -- @VK_QUERY_TYPE_VIDEO_ENCODE_FEEDBACK_KHR@, then there /must/ be no -- bound video session -- -- - #VUID-vkCmdBeginQuery-queryPool-01922# @queryPool@ /must/ have been -- created with a @queryType@ that differs from that of any queries -- that are -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-active active> -- within @commandBuffer@ -- -- - #VUID-vkCmdBeginQuery-queryType-07070# If the @queryType@ used to -- create @queryPool@ was -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MESH_PRIMITIVES_GENERATED_EXT' -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBeginQuery-queryType-02327# 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 -- -- - #VUID-vkCmdBeginQuery-queryType-02328# 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 -- -- - #VUID-vkCmdBeginQuery-queryType-06687# If the @queryType@ used to -- create @queryPool@ was -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBeginQuery-queryType-06688# If the @queryType@ used to -- create @queryPool@ was -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PRIMITIVES_GENERATED_EXT' -- then -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-primitivesGeneratedQuery primitivesGeneratedQuery> -- /must/ be enabled -- -- - #VUID-vkCmdBeginQuery-queryPool-07289# If @queryPool@ was created -- with a @queryType@ of -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR', -- then the -- 'Vulkan.Extensions.VK_KHR_performance_query.QueryPoolPerformanceCreateInfoKHR'::@queueFamilyIndex@ -- @queryPool@ was created with /must/ equal the queue family index of -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from -- -- - #VUID-vkCmdBeginQuery-queryPool-03223# 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@ -- -- - #VUID-vkCmdBeginQuery-queryPool-03224# 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@ -- -- - #VUID-vkCmdBeginQuery-queryPool-03225# 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 -- -- - #VUID-vkCmdBeginQuery-queryPool-03226# 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 -- -- - #VUID-vkCmdBeginQuery-None-02863# 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) -- -- - #VUID-vkCmdBeginQuery-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBeginQuery-queryPool-parameter# @queryPool@ /must/ be a -- valid 'Vulkan.Core10.Handles.QueryPool' handle -- -- - #VUID-vkCmdBeginQuery-flags-parameter# @flags@ /must/ be a valid -- combination of -- 'Vulkan.Core10.Enums.QueryControlFlagBits.QueryControlFlagBits' -- values -- -- - #VUID-vkCmdBeginQuery-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBeginQuery-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, decode, or encode -- operations -- -- - #VUID-vkCmdBeginQuery-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Both | Graphics | Action | -- | Secondary | | | Compute | State | -- | | | | Decode | | -- | | | | Encode | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.QueryControlFlagBits.QueryControlFlags', -- 'Vulkan.Core10.Handles.QueryPool', -- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginQueryIndexedEXT', -- 'cmdEndQuery', -- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT' 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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> QueryControlFlags -> io () cmdBeginQuery CommandBuffer commandBuffer QueryPool queryPool "firstViewport" ::: Word32 query QueryControlFlags flags = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> QueryPool -> ("firstViewport" ::: Word32) -> QueryControlFlags -> IO ()) vkCmdBeginQueryPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBeginQuery is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBeginQuery" (Ptr CommandBuffer_T -> QueryPool -> ("firstViewport" ::: Word32) -> QueryControlFlags -> IO () vkCmdBeginQuery' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (QueryPool queryPool) ("firstViewport" ::: Word32 query) (QueryControlFlags flags)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 :: forall (io :: * -> *) r. MonadIO io => CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> QueryControlFlags -> io r -> io r cmdUseQuery CommandBuffer commandBuffer QueryPool queryPool "firstViewport" ::: Word32 query QueryControlFlags flags io r a = (forall (io :: * -> *). MonadIO io => CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> QueryControlFlags -> io () cmdBeginQuery CommandBuffer commandBuffer QueryPool queryPool "firstViewport" ::: Word32 query QueryControlFlags flags) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> io r a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* (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 -- -- The command completes the query in @queryPool@ identified by @query@, -- and marks it as available. -- -- This command defines an execution dependency between other query -- commands that reference the same query. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @query@ that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- -- The second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes only the operation of this command. -- -- Calling 'cmdEndQuery' is equivalent to calling -- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT' with -- the @index@ parameter set to zero. -- -- == Valid Usage -- -- - #VUID-vkCmdEndQuery-None-01923# All queries used by the command -- /must/ be -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-active active> -- -- - #VUID-vkCmdEndQuery-query-00810# @query@ /must/ be less than the -- number of queries in @queryPool@ -- -- - #VUID-vkCmdEndQuery-commandBuffer-01886# @commandBuffer@ /must/ not -- be a protected command buffer -- -- - #VUID-vkCmdEndQuery-query-00812# 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@ -- -- - #VUID-vkCmdEndQuery-queryPool-03227# 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@ -- -- - #VUID-vkCmdEndQuery-queryPool-03228# 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 -- -- - #VUID-vkCmdEndQuery-None-07007# If called within a subpass of a -- render pass instance, the corresponding 'cmdBeginQuery'* command -- /must/ have been called previously within the same subpass -- -- - #VUID-vkCmdEndQuery-None-07008# If called outside of a render pass -- instance, the corresponding 'cmdBeginQuery'* command /must/ have -- been called outside of a render pass instance -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdEndQuery-commandBuffer-parameter# @commandBuffer@ /must/ -- be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdEndQuery-queryPool-parameter# @queryPool@ /must/ be a -- valid 'Vulkan.Core10.Handles.QueryPool' handle -- -- - #VUID-vkCmdEndQuery-commandBuffer-recording# @commandBuffer@ /must/ -- be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdEndQuery-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, decode, or encode -- operations -- -- - #VUID-vkCmdEndQuery-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Both | Graphics | Action | -- | Secondary | | | Compute | State | -- | | | | Decode | | -- | | | | Encode | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Handles.QueryPool', 'cmdBeginQuery', -- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginQueryIndexedEXT', -- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT' 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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> io () cmdEndQuery CommandBuffer commandBuffer QueryPool queryPool "firstViewport" ::: Word32 query = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> QueryPool -> ("firstViewport" ::: Word32) -> IO ()) vkCmdEndQueryPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdEndQuery is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdEndQuery" (Ptr CommandBuffer_T -> QueryPool -> ("firstViewport" ::: Word32) -> IO () vkCmdEndQuery' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (QueryPool queryPool) ("firstViewport" ::: Word32 query)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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. -- -- This command defines an execution dependency between other query -- commands that reference the same query. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @firstQuery@ and @queryCount@ that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- -- The second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @firstQuery@ and @queryCount@ that occur later in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- -- The operation of this command happens after the first scope and happens -- before the second scope. -- -- 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 -- -- - #VUID-vkCmdResetQueryPool-firstQuery-00796# @firstQuery@ /must/ be -- less than the number of queries in @queryPool@ -- -- - #VUID-vkCmdResetQueryPool-firstQuery-00797# The sum of @firstQuery@ -- and @queryCount@ /must/ be less than or equal to the number of -- queries in @queryPool@ -- -- - #VUID-vkCmdResetQueryPool-None-02841# All queries used by the -- command /must/ not be active -- -- - #VUID-vkCmdResetQueryPool-firstQuery-02862# 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) -- -- - #VUID-vkCmdResetQueryPool-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdResetQueryPool-queryPool-parameter# @queryPool@ /must/ be -- a valid 'Vulkan.Core10.Handles.QueryPool' handle -- -- - #VUID-vkCmdResetQueryPool-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdResetQueryPool-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, decode, encode, or -- optical flow operations -- -- - #VUID-vkCmdResetQueryPool-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdResetQueryPool-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdResetQueryPool-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | Secondary | | | Compute | | -- | | | | Decode | | -- | | | | Encode | | -- | | | | Opticalflow | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdResetQueryPool CommandBuffer commandBuffer QueryPool queryPool "firstViewport" ::: Word32 firstQuery "firstViewport" ::: Word32 queryCount = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> QueryPool -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdResetQueryPoolPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdResetQueryPool is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdResetQueryPool" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- When 'cmdWriteTimestamp' is submitted to a queue, it defines an -- execution dependency on commands that were submitted before it, and -- writes a timestamp to a query pool. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- The synchronization scope is limited to operations on the pipeline stage -- specified by @pipelineStage@. -- -- The second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes only the timestamp write operation. -- -- Note -- -- Implementations may write the timestamp at any stage that is -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically later> -- than @stage@. -- -- Any timestamp write that -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-execution happens-after> -- another timestamp write in the same submission /must/ not have a lower -- value unless its value overflows the maximum supported integer bit width -- of the query. If @VK_EXT_calibrated_timestamps@ is enabled, this extends -- to timestamp writes across all submissions on the same logical device: -- any timestamp write that -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-execution happens-after> -- another /must/ not have a lower value unless its value overflows the -- maximum supported integer bit width of the query. Timestamps written by -- this command /must/ be in the -- 'Vulkan.Extensions.VK_EXT_calibrated_timestamps.TIME_DOMAIN_DEVICE_EXT' -- <VkTimeDomainEXT.html time domain>. If an overflow occurs, the timestamp -- value /must/ wrap back to zero. -- -- Note -- -- Comparisons between timestamps should be done between timestamps where -- they are guaranteed to not decrease. For example, subtracting an older -- timestamp from a newer one to determine the execution time of a sequence -- of commands is only a reliable measurement if the two timestamp writes -- were performed in the same submission, or if the writes were performed -- on the same logical device and @VK_EXT_calibrated_timestamps@ is -- enabled. -- -- 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 -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04074# @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 -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04075# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04076# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- 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' -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04077# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04078# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04079# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-04080# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-07077# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-vkCmdWriteTimestamp-shadingRateImage-07314# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-vkCmdWriteTimestamp-synchronization2-06489# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_NONE' -- -- - #VUID-vkCmdWriteTimestamp-rayTracingPipeline-07943# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @pipelineStage@ /must/ not be -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-vkCmdWriteTimestamp-queryPool-01416# @queryPool@ /must/ have -- been created with a @queryType@ of -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_TIMESTAMP' -- -- - #VUID-vkCmdWriteTimestamp-timestampValidBits-00829# The command -- pool’s queue family /must/ support a non-zero @timestampValidBits@ -- -- - #VUID-vkCmdWriteTimestamp-query-04904# @query@ /must/ be less than -- the number of queries in @queryPool@ -- -- - #VUID-vkCmdWriteTimestamp-None-00830# All queries used by the -- command /must/ be /unavailable/ -- -- - #VUID-vkCmdWriteTimestamp-query-00831# 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) -- -- - #VUID-vkCmdWriteTimestamp-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdWriteTimestamp-pipelineStage-parameter# @pipelineStage@ -- /must/ be a valid -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- value -- -- - #VUID-vkCmdWriteTimestamp-queryPool-parameter# @queryPool@ /must/ be -- a valid 'Vulkan.Core10.Handles.QueryPool' handle -- -- - #VUID-vkCmdWriteTimestamp-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdWriteTimestamp-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, compute, decode, -- encode, or optical flow operations -- -- - #VUID-vkCmdWriteTimestamp-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Both | Transfer | Action | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- | | | | Decode | | -- | | | | Encode | | -- | | | | Opticalflow | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 a -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' value, -- 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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("stageMask" ::: PipelineStageFlags) -> QueryPool -> ("firstViewport" ::: Word32) -> io () cmdWriteTimestamp CommandBuffer commandBuffer "stageMask" ::: PipelineStageFlags pipelineStage QueryPool queryPool "firstViewport" ::: Word32 query = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("stageMask" ::: PipelineStageFlags) -> QueryPool -> ("firstViewport" ::: Word32) -> IO ()) vkCmdWriteTimestampPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdWriteTimestamp is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdWriteTimestamp" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- Any results written for a query are written according to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-memorylayout a layout dependent on the query type>. -- -- Results for any query in @queryPool@ identified by @firstQuery@ and -- @queryCount@ that is available are copied to @dstBuffer@. -- -- If -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT' -- is set, results for all queries in @queryPool@ identified by -- @firstQuery@ and @queryCount@ are copied to @dstBuffer@, along with an -- extra availability value written directly after the results of each -- query and interpreted as an unsigned integer. A value of zero indicates -- that the results are not yet available, otherwise the query is complete -- and results are available. -- -- If @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@ is set, results for all queries -- in @queryPool@ identified by @firstQuery@ and @queryCount@ are copied to -- @dstBuffer@, along with an extra status value written directly after the -- results of each query and interpreted as a signed integer. A value of -- zero indicates that the results are not yet available. Positive values -- indicate that the operations within the query completed successfully, -- and the query results are valid. Negative values indicate that the -- operations within the query completed unsuccessfully. -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryResultStatusKHR VkQueryResultStatusKHR> -- defines specific meaning for values returned here, though -- implementations are free to return other values. -- -- Results for any available query written by this command are final and -- represent the final result of the query. If -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT' is -- set, then for any query that is unavailable, an intermediate result -- between zero and the final result value is written for that query. -- Otherwise, any result written by this command is undefined. -- -- If 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set, -- results and availability or status values for all queries are written as -- an array of 64-bit values. If the @queryPool@ was created with -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR', -- results for each query are written as an array of the type indicated by -- 'Vulkan.Extensions.VK_KHR_performance_query.PerformanceCounterKHR'::@storage@ -- for the counter being queried. Otherwise, results and availability or -- status values are written as an array of 32-bit values. If an unsigned -- integer query’s value overflows the result type, the value /may/ either -- wrap or saturate. If a signed integer query’s value overflows the result -- type, the value is undefined. If a floating point query’s value is not -- representable as the result type, the value is undefined. -- -- This command defines an execution dependency between other query -- commands that reference the same query. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @query@ that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- If @flags@ does not include -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WAIT_BIT', -- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT', -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWriteTimestamp2', -- 'cmdEndQuery', and 'cmdWriteTimestamp' are excluded from this scope. -- -- The second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes all commands which reference the queries in @queryPool@ -- indicated by @query@ that occur later in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order>. -- -- The operation of this command happens after the first scope and happens -- before the second scope. -- -- '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 -- -- - #VUID-vkCmdCopyQueryPoolResults-dstOffset-00819# @dstOffset@ /must/ -- be less than the size of @dstBuffer@ -- -- - #VUID-vkCmdCopyQueryPoolResults-firstQuery-00820# @firstQuery@ -- /must/ be less than the number of queries in @queryPool@ -- -- - #VUID-vkCmdCopyQueryPoolResults-firstQuery-00821# The sum of -- @firstQuery@ and @queryCount@ /must/ be less than or equal to the -- number of queries in @queryPool@ -- -- - #VUID-vkCmdCopyQueryPoolResults-flags-00822# If -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is not -- set in @flags@ then @dstOffset@ and @stride@ /must/ be multiples of -- @4@ -- -- - #VUID-vkCmdCopyQueryPoolResults-flags-00823# If -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' is set -- in @flags@ then @dstOffset@ and @stride@ /must/ be multiples of @8@ -- -- - #VUID-vkCmdCopyQueryPoolResults-dstBuffer-00824# @dstBuffer@ /must/ -- have enough storage, from @dstOffset@, to contain the result of each -- query, as described -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-memorylayout here> -- -- - #VUID-vkCmdCopyQueryPoolResults-dstBuffer-00825# @dstBuffer@ /must/ -- have been created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - #VUID-vkCmdCopyQueryPoolResults-dstBuffer-00826# If @dstBuffer@ is -- non-sparse then it /must/ be bound completely and contiguously to a -- single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdCopyQueryPoolResults-queryType-00827# 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' -- -- - #VUID-vkCmdCopyQueryPoolResults-queryType-03232# 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' -- -- - #VUID-vkCmdCopyQueryPoolResults-queryType-03233# 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', -- @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@, -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_PARTIAL_BIT', -- or 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_64_BIT' -- -- - #VUID-vkCmdCopyQueryPoolResults-queryType-03234# 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' -- -- - #VUID-vkCmdCopyQueryPoolResults-queryType-02734# -- 'cmdCopyQueryPoolResults' /must/ not be called if the @queryType@ -- used to create @queryPool@ was -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_INTEL' -- -- - #VUID-vkCmdCopyQueryPoolResults-queryType-06901# If the @queryType@ -- used to create @queryPool@ was -- @VK_QUERY_TYPE_RESULT_STATUS_ONLY_KHR@, then @flags@ /must/ include -- @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@ -- -- - #VUID-vkCmdCopyQueryPoolResults-flags-06902# If @flags@ includes -- @VK_QUERY_RESULT_WITH_STATUS_BIT_KHR@, then it /must/ not include -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QUERY_RESULT_WITH_AVAILABILITY_BIT' -- -- - #VUID-vkCmdCopyQueryPoolResults-None-07429# All queries used by the -- command /must/ not be active -- -- - #VUID-vkCmdCopyQueryPoolResults-None-08752# All queries used by the -- command /must/ have been made /available/ by prior executed commands -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdCopyQueryPoolResults-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdCopyQueryPoolResults-queryPool-parameter# @queryPool@ -- /must/ be a valid 'Vulkan.Core10.Handles.QueryPool' handle -- -- - #VUID-vkCmdCopyQueryPoolResults-dstBuffer-parameter# @dstBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - #VUID-vkCmdCopyQueryPoolResults-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.QueryResultFlagBits.QueryResultFlagBits' values -- -- - #VUID-vkCmdCopyQueryPoolResults-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdCopyQueryPoolResults-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - #VUID-vkCmdCopyQueryPoolResults-renderpass# This command /must/ only -- be called outside of a render pass instance -- -- - #VUID-vkCmdCopyQueryPoolResults-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- - #VUID-vkCmdCopyQueryPoolResults-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | Secondary | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> QueryPool -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> Buffer -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> QueryResultFlags -> io () cmdCopyQueryPoolResults CommandBuffer commandBuffer QueryPool queryPool "firstViewport" ::: Word32 firstQuery "firstViewport" ::: Word32 queryCount Buffer dstBuffer "offset" ::: DeviceSize dstOffset "offset" ::: DeviceSize stride QueryResultFlags flags = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) 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 forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdCopyQueryPoolResults is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdCopyQueryPoolResults" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- When a command buffer begins recording, all push constant values are -- undefined. Reads of undefined push constant values by the executing -- shader return undefined values. -- -- Push constant values /can/ be updated incrementally, causing shader -- stages in @stageFlags@ to read the new data from @pValues@ for push -- constants modified by this command, while still reading the previous -- data for push constants not modified by this command. When a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#pipelines-bindpoint-commands bound pipeline command> -- is issued, the bound pipeline’s layout /must/ be compatible with the -- layouts used to set the values of all push constants in the pipeline -- layout’s push constant ranges, as described in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility>. -- Binding a pipeline with a layout that is not compatible with the push -- constant layout does not disturb the push constant values. -- -- 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 -- -- - #VUID-vkCmdPushConstants-offset-01795# 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 -- -- - #VUID-vkCmdPushConstants-offset-01796# 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@ -- -- - #VUID-vkCmdPushConstants-offset-00368# @offset@ /must/ be a multiple -- of @4@ -- -- - #VUID-vkCmdPushConstants-size-00369# @size@ /must/ be a multiple of -- @4@ -- -- - #VUID-vkCmdPushConstants-offset-00370# @offset@ /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@ -- -- - #VUID-vkCmdPushConstants-size-00371# @size@ /must/ be less than or -- equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@ -- minus @offset@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdPushConstants-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdPushConstants-layout-parameter# @layout@ /must/ be a -- valid 'Vulkan.Core10.Handles.PipelineLayout' handle -- -- - #VUID-vkCmdPushConstants-stageFlags-parameter# @stageFlags@ /must/ -- be a valid combination of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' values -- -- - #VUID-vkCmdPushConstants-stageFlags-requiredbitmask# @stageFlags@ -- /must/ not be @0@ -- -- - #VUID-vkCmdPushConstants-pValues-parameter# @pValues@ /must/ be a -- valid pointer to an array of @size@ bytes -- -- - #VUID-vkCmdPushConstants-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdPushConstants-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - #VUID-vkCmdPushConstants-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdPushConstants-size-arraylength# @size@ /must/ be greater -- than @0@ -- -- - #VUID-vkCmdPushConstants-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> PipelineLayout -> ShaderStageFlags -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("data" ::: Ptr ()) -> io () cmdPushConstants CommandBuffer commandBuffer PipelineLayout layout ShaderStageFlags stageFlags "firstViewport" ::: Word32 offset "firstViewport" ::: Word32 size "data" ::: Ptr () values = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> PipelineLayout -> ShaderStageFlags -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("data" ::: Ptr ()) -> IO ()) vkCmdPushConstantsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdPushConstants is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdPushConstants" (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)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-00895# 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' -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-01758# 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' -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-02842# 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' -- -- - #VUID-vkCmdBeginRenderPass-stencilInitialLayout-02843# 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' -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-00897# 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' -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-00898# 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' -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-00899# 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' -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-00900# If the -- @initialLayout@ member of any 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@ -- -- - #VUID-vkCmdBeginRenderPass-srcStageMask-06451# The @srcStageMask@ -- 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 -- -- - #VUID-vkCmdBeginRenderPass-dstStageMask-06452# The @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 -- -- - #VUID-vkCmdBeginRenderPass-framebuffer-02532# 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 -- -- - #VUID-vkCmdBeginRenderPass-framebuffer-09045# If any attachments -- specified in @framebuffer@ are used by @renderPass@ and are bound to -- overlapping memory locations, there /must/ be only one that is used -- as a color attachment, depth\/stencil, or resolve attachment in any -- subpass -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-07000# 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_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- 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 either the -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT' -- or -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT' -- and either the -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT' -- or 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT' -- usage bits -- -- - #VUID-vkCmdBeginRenderPass-initialLayout-07001# 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_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- then the corresponding attachment image view of the framebuffer -- specified in the @framebuffer@ member of @pRenderPassBegin@ /must/ -- have been created with a @usage@ value the -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT' -- usage bit -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdBeginRenderPass-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBeginRenderPass-pRenderPassBegin-parameter# -- @pRenderPassBegin@ /must/ be a valid pointer to a valid -- 'RenderPassBeginInfo' structure -- -- - #VUID-vkCmdBeginRenderPass-contents-parameter# @contents@ /must/ be -- a valid 'Vulkan.Core10.Enums.SubpassContents.SubpassContents' value -- -- - #VUID-vkCmdBeginRenderPass-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBeginRenderPass-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBeginRenderPass-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdBeginRenderPass-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdBeginRenderPass-bufferlevel# @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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Graphics | Action | -- | | | | | State | -- | | | | | Synchronization | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (a :: [*]) (io :: * -> *). (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io () cmdBeginRenderPass CommandBuffer commandBuffer RenderPassBeginInfo a renderPassBegin SubpassContents contents = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCmdBeginRenderPassPtr :: FunPtr (Ptr CommandBuffer_T -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo)) -> SubpassContents -> IO ()) vkCmdBeginRenderPassPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo)) -> SubpassContents -> IO ()) pVkCmdBeginRenderPass (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo)) -> SubpassContents -> IO ()) vkCmdBeginRenderPassPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBeginRenderPass is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (RenderPassBeginInfo a renderPassBegin) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBeginRenderPass" (Ptr CommandBuffer_T -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo)) -> SubpassContents -> IO () vkCmdBeginRenderPass' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions Ptr (RenderPassBeginInfo a) pRenderPassBegin) (SubpassContents contents)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 :: forall (a :: [*]) (io :: * -> *) r. (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io r -> io r cmdUseRenderPass CommandBuffer commandBuffer RenderPassBeginInfo a pRenderPassBegin SubpassContents contents io r a = (forall (a :: [*]) (io :: * -> *). (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassContents -> io () cmdBeginRenderPass CommandBuffer commandBuffer RenderPassBeginInfo a pRenderPassBegin SubpassContents contents) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> io r a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* (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. -- -- After transitioning to the next subpass, the application /can/ record -- the commands for that subpass. -- -- == Valid Usage -- -- - #VUID-vkCmdNextSubpass-None-00909# The current subpass index /must/ -- be less than the number of subpasses in the render pass minus one -- -- - #VUID-vkCmdNextSubpass-None-02349# This command /must/ not be -- recorded when transform feedback is active -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdNextSubpass-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdNextSubpass-contents-parameter# @contents@ /must/ be a -- valid 'Vulkan.Core10.Enums.SubpassContents.SubpassContents' value -- -- - #VUID-vkCmdNextSubpass-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdNextSubpass-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdNextSubpass-renderpass# This command /must/ only be -- called inside of a render pass instance -- -- - #VUID-vkCmdNextSubpass-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdNextSubpass-bufferlevel# @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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | | | | | State | -- | | | | | Synchronization | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> SubpassContents -> io () cmdNextSubpass CommandBuffer commandBuffer SubpassContents contents = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> SubpassContents -> IO ()) vkCmdNextSubpassPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdNextSubpass is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdNextSubpass" (Ptr CommandBuffer_T -> SubpassContents -> IO () vkCmdNextSubpass' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (SubpassContents contents)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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 -- -- - #VUID-vkCmdEndRenderPass-None-00910# The current subpass index -- /must/ be equal to the number of subpasses in the render pass minus -- one -- -- - #VUID-vkCmdEndRenderPass-None-02351# This command /must/ not be -- recorded when transform feedback is active -- -- - #VUID-vkCmdEndRenderPass-None-06170# The current render pass -- instance /must/ not have been begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdEndRenderPass-None-07004# If 'cmdBeginQuery'* was called -- within a subpass of the render pass, the corresponding -- 'cmdEndQuery'* /must/ have been called subsequently within the same -- subpass -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdEndRenderPass-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdEndRenderPass-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdEndRenderPass-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdEndRenderPass-renderpass# This command /must/ only be -- called inside of a render pass instance -- -- - #VUID-vkCmdEndRenderPass-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdEndRenderPass-bufferlevel# @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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Inside | Outside | Graphics | Action | -- | | | | | State | -- | | | | | Synchronization | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> io () cmdEndRenderPass CommandBuffer commandBuffer = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdEndRenderPassPtr :: FunPtr (Ptr CommandBuffer_T -> IO ()) vkCmdEndRenderPassPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ()) pVkCmdEndRenderPass (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> IO ()) vkCmdEndRenderPassPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdEndRenderPass is null" forall a. Maybe a Nothing 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 forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdEndRenderPass" (Ptr CommandBuffer_T -> IO () vkCmdEndRenderPass' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#commandbuffers-lifecycle executable or recording state>, -- that primary command buffer becomes -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#commandbuffers-lifecycle invalid>. -- -- If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nestedCommandBuffer nestedCommandBuffer> -- feature is enabled it is valid usage for 'cmdExecuteCommands' to also be -- recorded to a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary secondary command buffer>. -- -- == Valid Usage -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00088# Each element of -- @pCommandBuffers@ /must/ have been allocated with a @level@ of -- 'Vulkan.Core10.Enums.CommandBufferLevel.COMMAND_BUFFER_LEVEL_SECONDARY' -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00089# Each element of -- @pCommandBuffers@ /must/ be in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#commandbuffers-lifecycle pending or executable state> -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00091# 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#commandbuffers-lifecycle pending state> -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00092# 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@ -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00093# 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@ -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00094# 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 -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00096# 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' -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00099# 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 -- -- - #VUID-vkCmdExecuteCommands-contents-06018# If 'cmdExecuteCommands' -- is being called within a render pass instance begun with -- 'cmdBeginRenderPass', its @contents@ parameter /must/ have been set -- to -- 'Vulkan.Core10.Enums.SubpassContents.SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS' -- , or -- 'Vulkan.Core10.Enums.SubpassContents.SUBPASS_CONTENTS_INLINE_AND_SECONDARY_COMMAND_BUFFERS_EXT' -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-06019# If -- 'cmdExecuteCommands' is being called within a render pass instance -- begun with 'cmdBeginRenderPass', 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 -- -- - #VUID-vkCmdExecuteCommands-pBeginInfo-06020# If 'cmdExecuteCommands' -- is being called within a render pass instance begun with -- 'cmdBeginRenderPass', 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://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-compatibility compatible> -- with the current render pass -- -- - #VUID-vkCmdExecuteCommands-pNext-02865# 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' -- -- - #VUID-vkCmdExecuteCommands-pNext-02866# 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@ -- -- - #VUID-vkCmdExecuteCommands-pNext-02867# 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@ -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00100# 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' -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-00101# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-inheritedQueries inheritedQueries> -- feature is not enabled, @commandBuffer@ /must/ not have any queries -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-active active> -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-00102# If @commandBuffer@ -- has a 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' query -- <https://registry.khronos.org/vulkan/specs/1.3-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' -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-00103# If @commandBuffer@ -- has a 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' query -- <https://registry.khronos.org/vulkan/specs/1.3-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 -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-00104# If @commandBuffer@ -- has a 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS' -- query -- <https://registry.khronos.org/vulkan/specs/1.3-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 -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-00105# Each element of -- @pCommandBuffers@ /must/ not begin any query types that are -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-active active> -- in @commandBuffer@ -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-07594# @commandBuffer@ -- /must/ not have any queries other than -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' and -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS' -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#queries-operation-active active> -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-01820# If @commandBuffer@ -- is a protected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, each element of @pCommandBuffers@ /must/ be a -- protected command buffer -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-01821# If @commandBuffer@ -- is an unprotected command buffer and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, each element of @pCommandBuffers@ /must/ be an -- unprotected command buffer -- -- - #VUID-vkCmdExecuteCommands-None-02286# This command /must/ not be -- recorded when transform feedback is active -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-06533# If -- 'cmdExecuteCommands' is being called within a render pass instance -- and any recorded command in @commandBuffer@ in the current subpass -- will write to an image subresource as an attachment, commands -- recorded in elements of @pCommandBuffers@ /must/ not read from the -- memory backing that image subresource in any other way -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-06534# If -- 'cmdExecuteCommands' is being called within a render pass instance -- and any recorded command in @commandBuffer@ in the current subpass -- will read from an image subresource used as an attachment in any way -- other than as an attachment, commands recorded in elements of -- @pCommandBuffers@ /must/ not write to that image subresource as an -- attachment -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-06535# If -- 'cmdExecuteCommands' is being called within a render pass instance -- and any recorded command in a given element of @pCommandBuffers@ -- will write to an image subresource as an attachment, commands -- recorded in elements of @pCommandBuffers@ at a higher index /must/ -- not read from the memory backing that image subresource in any other -- way -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-06536# If -- 'cmdExecuteCommands' is being called within a render pass instance -- and any recorded command in a given element of @pCommandBuffers@ -- will read from an image subresource used as an attachment in any way -- other than as an attachment, commands recorded in elements of -- @pCommandBuffers@ at a higher index /must/ not write to that image -- subresource as an attachment -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-06021# If -- @pCommandBuffers@ contains any -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-suspension suspended render pass instances>, -- there /must/ be no action or synchronization commands between that -- render pass instance and any render pass instance that resumes it -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-06022# If -- @pCommandBuffers@ contains any -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-suspension suspended render pass instances>, -- there /must/ be no render pass instances between that render pass -- instance and any render pass instance that resumes it -- -- - #VUID-vkCmdExecuteCommands-variableSampleLocations-06023# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-variableSampleLocations variableSampleLocations> -- limit is not supported, and any element of @pCommandBuffers@ -- contains any -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-suspension suspended render pass instances>, -- where a graphics pipeline has been bound, any pipelines bound in the -- render pass instance that resumes it, or any subsequent render pass -- instances that resume from that one and so on, /must/ use the same -- sample locations -- -- - #VUID-vkCmdExecuteCommands-flags-06024# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- its -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@flags@ -- parameter /must/ have included -- 'Vulkan.Core13.Enums.RenderingFlagBits.RENDERING_CONTENTS_SECONDARY_COMMAND_BUFFERS_BIT' -- -- - #VUID-vkCmdExecuteCommands-pBeginInfo-06025# If 'cmdExecuteCommands' -- is being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- 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 -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdExecuteCommands-flags-06026# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @flags@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@flags@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- excluding -- 'Vulkan.Core13.Enums.RenderingFlagBits.RENDERING_CONTENTS_SECONDARY_COMMAND_BUFFERS_BIT' -- -- - #VUID-vkCmdExecuteCommands-colorAttachmentCount-06027# If -- 'cmdExecuteCommands' is being called within a render pass instance -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @colorAttachmentCount@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@colorAttachmentCount@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdExecuteCommands-imageView-06028# If 'cmdExecuteCommands' -- is being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- if the @imageView@ member of an element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the corresponding -- element of the @pColorAttachmentFormats@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the format used to create that image view -- -- - #VUID-vkCmdExecuteCommands-imageView-07606# If 'cmdExecuteCommands' -- is being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- if the @imageView@ member of an element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is 'Vulkan.Core10.APIConstants.NULL_HANDLE', the corresponding -- element of the @pColorAttachmentFormats@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdExecuteCommands-pDepthAttachment-06029# If -- 'cmdExecuteCommands' is being called within a render pass instance -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- if the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthAttachmentFormat@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the format used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pStencilAttachment-06030# If -- 'cmdExecuteCommands' is being called within a render pass instance -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- if the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @stencilAttachmentFormat@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the format used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pDepthAttachment-06774# If -- 'cmdExecuteCommands' is being called within a render pass instance -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthAttachmentFormat@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdExecuteCommands-pStencilAttachment-06775# If -- 'cmdExecuteCommands' is being called within a render pass instance -- begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- was 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @stencilAttachmentFormat@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-vkCmdExecuteCommands-viewMask-06031# If 'cmdExecuteCommands' -- is being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- the @viewMask@ member of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@viewMask@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- -- - #VUID-vkCmdExecuteCommands-pNext-06032# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' includes -- a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, if the @imageView@ member of an element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the corresponding -- element of the @pColorAttachmentSamples@ member of the -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the sample count used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pNext-06033# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' includes -- a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, if the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of the -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the sample count used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pNext-06034# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' includes -- a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, if the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of the -- @depthStencilAttachmentSamples@ member of the -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferBeginInfo'::@pInheritanceInfo@ -- used to begin recording each element of @pCommandBuffers@ /must/ be -- equal to the sample count used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pNext-06035# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' does not -- include a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, if the @imageView@ member of an element of the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pColorAttachments@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo'::@rasterizationSamples@ -- /must/ be equal to the sample count used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pNext-06036# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' does not -- include a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, if the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pDepthAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo'::@rasterizationSamples@ -- /must/ be equal to the sample count used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pNext-06037# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' does not -- include a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, if the -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.RenderingInfo'::@pStencilAttachment->imageView@ -- parameter to -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo'::@rasterizationSamples@ -- /must/ be equal to the sample count used to create that image view -- -- - #VUID-vkCmdExecuteCommands-pNext-09299# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering', -- with any color attachment using a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' used to -- create each element of @pCommandBuffers@ /must/ include a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID' -- structure with a @externalFormat@ matching that used to create the -- resolve attachment in the render pass -- -- - #VUID-vkCmdExecuteCommands-pNext-09300# If 'cmdExecuteCommands' is -- being called within a render pass instance begun with -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.cmdBeginRendering' -- with any color attachment using a resolve mode of -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID', -- and the @pNext@ chain of -- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo' does not -- include a -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoAMD' -- or -- 'Vulkan.Extensions.VK_KHR_dynamic_rendering.AttachmentSampleCountInfoNV' -- structure, the value of -- 'Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering.CommandBufferInheritanceRenderingInfo'::@rasterizationSamples@ -- /must/ be -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-09375# @commandBuffer@ -- /must/ not be a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary secondary command buffer> -- unless the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nestedCommandBuffer nestedCommandBuffer> -- feature is enabled -- -- - #VUID-vkCmdExecuteCommands-nestedCommandBuffer-09376# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nestedCommandBuffer nestedCommandBuffer> -- feature is enabled, the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary command buffer nesting level> -- of each element of @pCommandBuffers@ /must/ be less than -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxCommandBufferNestingLevel maxCommandBufferNestingLevel> -- -- - #VUID-vkCmdExecuteCommands-nestedCommandBufferRendering-09377# If -- the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nestedCommandBufferRendering nestedCommandBufferRendering> -- feature is not enabled, and @commandBuffer@ is a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary secondary command buffer>, -- @commandBuffer@ /must/ not have been recorded with -- 'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_RENDER_PASS_CONTINUE_BIT' -- -- - #VUID-vkCmdExecuteCommands-nestedCommandBufferSimultaneousUse-09378# -- If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nestedCommandBufferSimultaneousUse nestedCommandBufferSimultaneousUse> -- feature is not enabled, and @commandBuffer@ is a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary secondary command buffer>, -- each element of @pCommandBuffers@ /must/ not have been recorded with -- 'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT' -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdExecuteCommands-pCommandBuffers-parameter# -- @pCommandBuffers@ /must/ be a valid pointer to an array of -- @commandBufferCount@ valid 'Vulkan.Core10.Handles.CommandBuffer' -- handles -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdExecuteCommands-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - #VUID-vkCmdExecuteCommands-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- - #VUID-vkCmdExecuteCommands-commandBufferCount-arraylength# -- @commandBufferCount@ /must/ be greater than @0@ -- -- - #VUID-vkCmdExecuteCommands-commonparent# 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#vkCmdBeginVideoCodingKHR Video Coding 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#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Transfer | Indirection | -- | Secondary | | | Graphics | | -- | | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("commandBuffers" ::: Vector CommandBuffer) -> io () cmdExecuteCommands CommandBuffer commandBuffer "commandBuffers" ::: Vector CommandBuffer commandBuffers = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let 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 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)) -> IO ()) vkCmdExecuteCommandsPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdExecuteCommands is null" forall a. Maybe a Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @(Ptr CommandBuffer_T) ((forall a. Vector a -> Int Data.Vector.length ("commandBuffers" ::: Vector CommandBuffer commandBuffers)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i CommandBuffer e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T) pPCommandBuffers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr (Ptr CommandBuffer_T)) (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer e))) ("commandBuffers" ::: Vector CommandBuffer commandBuffers) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdExecuteCommands" (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)) -> IO () vkCmdExecuteCommands' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("commandBuffers" ::: Vector CommandBuffer commandBuffers)) :: Word32)) ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T) pPCommandBuffers)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall b. ClearRect -> (("pRects" ::: Ptr ClearRect) -> IO b) -> IO b withCStruct ClearRect x ("pRects" ::: Ptr ClearRect) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 24 forall a b. (a -> b) -> a -> b $ \"pRects" ::: Ptr ClearRect p -> 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 :: forall b. ("pRects" ::: Ptr ClearRect) -> ClearRect -> IO b -> IO b pokeCStruct "pRects" ::: Ptr ClearRect p ClearRect{"firstViewport" ::: Word32 Rect2D layerCount :: "firstViewport" ::: Word32 baseArrayLayer :: "firstViewport" ::: Word32 rect :: Rect2D $sel:layerCount:ClearRect :: ClearRect -> "firstViewport" ::: Word32 $sel:baseArrayLayer:ClearRect :: ClearRect -> "firstViewport" ::: Word32 $sel:rect:ClearRect :: ClearRect -> Rect2D ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Rect2D)) (Rect2D rect) forall a. Storable a => Ptr a -> a -> IO () poke (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) ("firstViewport" ::: Word32 baseArrayLayer) forall a. Storable a => Ptr a -> a -> IO () poke (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) ("firstViewport" ::: Word32 layerCount) IO b f cStructSize :: Int cStructSize = Int 24 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. ("pRects" ::: Ptr ClearRect) -> IO b -> IO b pokeZeroCStruct "pRects" ::: Ptr ClearRect p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Rect2D)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct ClearRect where peekCStruct :: ("pRects" ::: Ptr ClearRect) -> IO ClearRect peekCStruct "pRects" ::: Ptr ClearRect p = do Rect2D rect <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Rect2D (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Rect2D)) "firstViewport" ::: Word32 baseArrayLayer <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) "firstViewport" ::: Word32 layerCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pRects" ::: Ptr ClearRect p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ Rect2D -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ClearRect ClearRect Rect2D rect "firstViewport" ::: Word32 baseArrayLayer "firstViewport" ::: Word32 layerCount instance Storable ClearRect where sizeOf :: ClearRect -> Int sizeOf ~ClearRect _ = Int 24 alignment :: ClearRect -> Int alignment ~ClearRect _ = Int 4 peek :: ("pRects" ::: Ptr ClearRect) -> IO ClearRect peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pRects" ::: Ptr ClearRect) -> ClearRect -> IO () poke "pRects" ::: Ptr ClearRect ptr ClearRect poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pRects" ::: Ptr ClearRect ptr ClearRect poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ClearRect where zero :: ClearRect zero = Rect2D -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ClearRect ClearRect forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkImageSubresourceLayers - Structure specifying an image subresource -- layers -- -- == Valid Usage -- -- - #VUID-VkImageSubresourceLayers-aspectMask-00167# 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' -- -- - #VUID-VkImageSubresourceLayers-aspectMask-00168# @aspectMask@ /must/ -- not contain -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT' -- -- - #VUID-VkImageSubresourceLayers-aspectMask-02247# @aspectMask@ /must/ -- not include @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index -- /i/ -- -- - #VUID-VkImageSubresourceLayers-layerCount-09243# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- feature is not enabled, @layerCount@ /must/ not be -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' -- -- - #VUID-VkImageSubresourceLayers-layerCount-01700# If @layerCount@ is -- not 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', it /must/ -- be greater than 0 -- -- == Valid Usage (Implicit) -- -- - #VUID-VkImageSubresourceLayers-aspectMask-parameter# @aspectMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values -- -- - #VUID-VkImageSubresourceLayers-aspectMask-requiredbitmask# -- @aspectMask@ /must/ not be @0@ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'BufferImageCopy', -- 'Vulkan.Core13.Promoted_From_VK_KHR_copy_commands2.BufferImageCopy2', -- 'Vulkan.Extensions.VK_NV_copy_memory_indirect.CopyMemoryToImageIndirectCommandNV', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags', 'ImageBlit', -- 'Vulkan.Core13.Promoted_From_VK_KHR_copy_commands2.ImageBlit2', -- 'ImageCopy', -- 'Vulkan.Core13.Promoted_From_VK_KHR_copy_commands2.ImageCopy2', -- 'ImageResolve', -- 'Vulkan.Core13.Promoted_From_VK_KHR_copy_commands2.ImageResolve2', -- 'Vulkan.Extensions.VK_EXT_host_image_copy.ImageToMemoryCopyEXT', -- 'Vulkan.Extensions.VK_EXT_host_image_copy.MemoryToImageCopyEXT', -- 'Vulkan.Extensions.VK_NV_copy_memory_indirect.cmdCopyMemoryToImageIndirectNV' 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 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 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 :: forall b. ImageSubresourceLayers -> (Ptr ImageSubresourceLayers -> IO b) -> IO b withCStruct ImageSubresourceLayers x Ptr ImageSubresourceLayers -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 16 forall a b. (a -> b) -> a -> b $ \Ptr ImageSubresourceLayers p -> 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 :: forall b. Ptr ImageSubresourceLayers -> ImageSubresourceLayers -> IO b -> IO b pokeCStruct Ptr ImageSubresourceLayers p ImageSubresourceLayers{"firstViewport" ::: Word32 ImageAspectFlags layerCount :: "firstViewport" ::: Word32 baseArrayLayer :: "firstViewport" ::: Word32 mipLevel :: "firstViewport" ::: Word32 aspectMask :: ImageAspectFlags $sel:layerCount:ImageSubresourceLayers :: ImageSubresourceLayers -> "firstViewport" ::: Word32 $sel:baseArrayLayer:ImageSubresourceLayers :: ImageSubresourceLayers -> "firstViewport" ::: Word32 $sel:mipLevel:ImageSubresourceLayers :: ImageSubresourceLayers -> "firstViewport" ::: Word32 $sel:aspectMask:ImageSubresourceLayers :: ImageSubresourceLayers -> ImageAspectFlags ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags aspectMask) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) ("firstViewport" ::: Word32 mipLevel) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) ("firstViewport" ::: Word32 baseArrayLayer) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) ("firstViewport" ::: Word32 layerCount) IO b f cStructSize :: Int cStructSize = Int 16 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr ImageSubresourceLayers -> IO b -> IO b pokeZeroCStruct Ptr ImageSubresourceLayers p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct ImageSubresourceLayers where peekCStruct :: Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers peekCStruct Ptr ImageSubresourceLayers p = do ImageAspectFlags aspectMask <- forall a. Storable a => Ptr a -> IO a peek @ImageAspectFlags ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) "firstViewport" ::: Word32 mipLevel <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) "firstViewport" ::: Word32 baseArrayLayer <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) "firstViewport" ::: Word32 layerCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceLayers p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 _ = Int 16 alignment :: ImageSubresourceLayers -> Int alignment ~ImageSubresourceLayers _ = Int 4 peek :: Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr ImageSubresourceLayers -> ImageSubresourceLayers -> IO () poke Ptr ImageSubresourceLayers ptr ImageSubresourceLayers poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr ImageSubresourceLayers ptr ImageSubresourceLayers poked (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 forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkBufferCopy - Structure specifying a buffer copy operation -- -- == Valid Usage -- -- - #VUID-VkBufferCopy-size-01988# The @size@ /must/ be greater than @0@ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 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 :: forall b. BufferCopy -> (("pRegions" ::: Ptr BufferCopy) -> IO b) -> IO b withCStruct BufferCopy x ("pRegions" ::: Ptr BufferCopy) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 24 forall a b. (a -> b) -> a -> b $ \"pRegions" ::: Ptr BufferCopy p -> 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 :: forall b. ("pRegions" ::: Ptr BufferCopy) -> BufferCopy -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr BufferCopy p BufferCopy{"offset" ::: DeviceSize size :: "offset" ::: DeviceSize dstOffset :: "offset" ::: DeviceSize srcOffset :: "offset" ::: DeviceSize $sel:size:BufferCopy :: BufferCopy -> "offset" ::: DeviceSize $sel:dstOffset:BufferCopy :: BufferCopy -> "offset" ::: DeviceSize $sel:srcOffset:BufferCopy :: BufferCopy -> "offset" ::: DeviceSize ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr DeviceSize)) ("offset" ::: DeviceSize srcOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr DeviceSize)) ("offset" ::: DeviceSize dstOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceSize)) ("offset" ::: DeviceSize size) IO b f cStructSize :: Int cStructSize = Int 24 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. ("pRegions" ::: Ptr BufferCopy) -> IO b -> IO b pokeZeroCStruct "pRegions" ::: Ptr BufferCopy p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr DeviceSize)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr DeviceSize)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceSize)) (forall a. Zero a => a zero) IO b f instance FromCStruct BufferCopy where peekCStruct :: ("pRegions" ::: Ptr BufferCopy) -> IO BufferCopy peekCStruct "pRegions" ::: Ptr BufferCopy p = do "offset" ::: DeviceSize srcOffset <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr DeviceSize)) "offset" ::: DeviceSize dstOffset <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr DeviceSize)) "offset" ::: DeviceSize size <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize (("pRegions" ::: Ptr BufferCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceSize)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("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 _ = Int 24 alignment :: BufferCopy -> Int alignment ~BufferCopy _ = Int 8 peek :: ("pRegions" ::: Ptr BufferCopy) -> IO BufferCopy peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pRegions" ::: Ptr BufferCopy) -> BufferCopy -> IO () poke "pRegions" ::: Ptr BufferCopy ptr BufferCopy poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr BufferCopy ptr BufferCopy poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero BufferCopy where zero :: BufferCopy zero = ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> BufferCopy BufferCopy forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkImageCopy - Structure specifying an image copy operation -- -- == Valid Usage -- -- - #VUID-VkImageCopy-apiVersion-07940# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_sampler_ycbcr_conversion VK_KHR_sampler_ycbcr_conversion> -- extension is not enabled, and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties'::@apiVersion@ -- is less than Vulkan 1.1, the @aspectMask@ member of @srcSubresource@ -- and @dstSubresource@ /must/ match -- -- - #VUID-VkImageCopy-apiVersion-07941# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_maintenance1 VK_KHR_maintenance1> -- extension is not enabled, and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties'::@apiVersion@ -- is less than Vulkan 1.1, the @layerCount@ member of @srcSubresource@ -- and @dstSubresource@ /must/ match -- -- - #VUID-VkImageCopy-extent-06668# @extent.width@ /must/ not be 0 -- -- - #VUID-VkImageCopy-extent-06669# @extent.height@ /must/ not be 0 -- -- - #VUID-VkImageCopy-extent-06670# @extent.depth@ /must/ not be 0 -- -- == Valid Usage (Implicit) -- -- - #VUID-VkImageCopy-srcSubresource-parameter# @srcSubresource@ /must/ -- be a valid 'ImageSubresourceLayers' structure -- -- - #VUID-VkImageCopy-dstSubresource-parameter# @dstSubresource@ /must/ -- be a valid 'ImageSubresourceLayers' structure -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall b. ImageCopy -> (("pRegions" ::: Ptr ImageCopy) -> IO b) -> IO b withCStruct ImageCopy x ("pRegions" ::: Ptr ImageCopy) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 68 forall a b. (a -> b) -> a -> b $ \"pRegions" ::: Ptr ImageCopy p -> 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 :: forall b. ("pRegions" ::: Ptr ImageCopy) -> ImageCopy -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr ImageCopy p ImageCopy{ImageSubresourceLayers Offset3D Extent3D extent :: Extent3D dstOffset :: Offset3D dstSubresource :: ImageSubresourceLayers srcOffset :: Offset3D srcSubresource :: ImageSubresourceLayers $sel:extent:ImageCopy :: ImageCopy -> Extent3D $sel:dstOffset:ImageCopy :: ImageCopy -> Offset3D $sel:dstSubresource:ImageCopy :: ImageCopy -> ImageSubresourceLayers $sel:srcOffset:ImageCopy :: ImageCopy -> Offset3D $sel:srcSubresource:ImageCopy :: ImageCopy -> ImageSubresourceLayers ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers srcSubresource) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Offset3D)) (Offset3D srcOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers dstSubresource) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Offset3D)) (Offset3D dstOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Extent3D)) (Extent3D extent) IO b f cStructSize :: Int cStructSize = Int 68 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. ("pRegions" ::: Ptr ImageCopy) -> IO b -> IO b pokeZeroCStruct "pRegions" ::: Ptr ImageCopy p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Offset3D)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Offset3D)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Extent3D)) (forall a. Zero a => a zero) IO b f instance FromCStruct ImageCopy where peekCStruct :: ("pRegions" ::: Ptr ImageCopy) -> IO ImageCopy peekCStruct "pRegions" ::: Ptr ImageCopy p = do ImageSubresourceLayers srcSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) Offset3D srcOffset <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Offset3D)) ImageSubresourceLayers dstSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageSubresourceLayers)) Offset3D dstOffset <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Offset3D)) Extent3D extent <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Extent3D (("pRegions" ::: Ptr ImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Extent3D)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 Storable ImageCopy where sizeOf :: ImageCopy -> Int sizeOf ~ImageCopy _ = Int 68 alignment :: ImageCopy -> Int alignment ~ImageCopy _ = Int 4 peek :: ("pRegions" ::: Ptr ImageCopy) -> IO ImageCopy peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pRegions" ::: Ptr ImageCopy) -> ImageCopy -> IO () poke "pRegions" ::: Ptr ImageCopy ptr ImageCopy poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr ImageCopy ptr ImageCopy poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ImageCopy where zero :: ImageCopy zero = ImageSubresourceLayers -> Offset3D -> ImageSubresourceLayers -> Offset3D -> Extent3D -> ImageCopy ImageCopy forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkImageBlit - Structure specifying an image blit operation -- -- = Description -- -- For each element of the @pRegions@ array, a blit operation is performed -- for the specified source and destination regions. -- -- == Valid Usage -- -- - #VUID-VkImageBlit-aspectMask-00238# The @aspectMask@ member of -- @srcSubresource@ and @dstSubresource@ /must/ match -- -- - #VUID-VkImageBlit-layerCount-08800# If neither of the @layerCount@ -- members of @srcSubresource@ or @dstSubresource@ are -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the -- @layerCount@ members of @srcSubresource@ or @dstSubresource@ /must/ -- match -- -- - #VUID-VkImageBlit-maintenance5-08799# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- feature is not enabled, the @layerCount@ member of @srcSubresource@ -- or @dstSubresource@ /must/ not be -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' -- -- - #VUID-VkImageBlit-layerCount-08801# If one of the @layerCount@ -- members of @srcSubresource@ or @dstSubresource@ is -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the other -- member /must/ be either -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' or equal to the -- @arrayLayers@ member of the 'Vulkan.Core10.Image.ImageCreateInfo' -- used to create the image minus @baseArrayLayer@ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkImageBlit-srcSubresource-parameter# @srcSubresource@ /must/ -- be a valid 'ImageSubresourceLayers' structure -- -- - #VUID-VkImageBlit-dstSubresource-parameter# @dstSubresource@ /must/ -- be a valid 'ImageSubresourceLayers' structure -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall b. ImageBlit -> (("pRegions" ::: Ptr ImageBlit) -> IO b) -> IO b withCStruct ImageBlit x ("pRegions" ::: Ptr ImageBlit) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 80 forall a b. (a -> b) -> a -> b $ \"pRegions" ::: Ptr ImageBlit p -> 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 :: forall b. ("pRegions" ::: Ptr ImageBlit) -> ImageBlit -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr ImageBlit p ImageBlit{(Offset3D, Offset3D) ImageSubresourceLayers dstOffsets :: (Offset3D, Offset3D) dstSubresource :: ImageSubresourceLayers srcOffsets :: (Offset3D, Offset3D) srcSubresource :: ImageSubresourceLayers $sel:dstOffsets:ImageBlit :: ImageBlit -> (Offset3D, Offset3D) $sel:dstSubresource:ImageBlit :: ImageBlit -> ImageSubresourceLayers $sel:srcOffsets:ImageBlit :: ImageBlit -> (Offset3D, Offset3D) $sel:srcSubresource:ImageBlit :: ImageBlit -> ImageSubresourceLayers ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers srcSubresource) let pSrcOffsets' :: Ptr Offset3D pSrcOffsets' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr (FixedArray 2 Offset3D))) case ((Offset3D, Offset3D) srcOffsets) of (Offset3D e0, Offset3D e1) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pSrcOffsets' :: Ptr Offset3D) (Offset3D e0) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pSrcOffsets' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Offset3D) (Offset3D e1) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers dstSubresource) let pDstOffsets' :: Ptr Offset3D pDstOffsets' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (FixedArray 2 Offset3D))) case ((Offset3D, Offset3D) dstOffsets) of (Offset3D e0, Offset3D e1) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pDstOffsets' :: Ptr Offset3D) (Offset3D e0) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pDstOffsets' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Offset3D) (Offset3D e1) IO b f cStructSize :: Int cStructSize = Int 80 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. ("pRegions" ::: Ptr ImageBlit) -> IO b -> IO b pokeZeroCStruct "pRegions" ::: Ptr ImageBlit p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) let pSrcOffsets' :: Ptr Offset3D pSrcOffsets' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr (FixedArray 2 Offset3D))) case ((forall a. Zero a => a zero, forall a. Zero a => a zero)) of (Offset3D e0, Offset3D e1) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pSrcOffsets' :: Ptr Offset3D) (Offset3D e0) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pSrcOffsets' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Offset3D) (Offset3D e1) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) let pDstOffsets' :: Ptr Offset3D pDstOffsets' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (FixedArray 2 Offset3D))) case ((forall a. Zero a => a zero, forall a. Zero a => a zero)) of (Offset3D e0, Offset3D e1) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pDstOffsets' :: Ptr Offset3D) (Offset3D e0) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Offset3D pDstOffsets' forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Offset3D) (Offset3D e1) IO b f instance FromCStruct ImageBlit where peekCStruct :: ("pRegions" ::: Ptr ImageBlit) -> IO ImageBlit peekCStruct "pRegions" ::: Ptr ImageBlit p = do ImageSubresourceLayers srcSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) let psrcOffsets :: Ptr Offset3D psrcOffsets = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr @Offset3D (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr (FixedArray 2 Offset3D))) Offset3D srcOffsets0 <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D ((Ptr Offset3D psrcOffsets forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` Int 0 :: Ptr Offset3D)) Offset3D srcOffsets1 <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D ((Ptr Offset3D psrcOffsets forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` Int 12 :: Ptr Offset3D)) ImageSubresourceLayers dstSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr ImageSubresourceLayers)) let pdstOffsets :: Ptr Offset3D pdstOffsets = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr @Offset3D (("pRegions" ::: Ptr ImageBlit p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (FixedArray 2 Offset3D))) Offset3D dstOffsets0 <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D ((Ptr Offset3D pdstOffsets forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` Int 0 :: Ptr Offset3D)) Offset3D dstOffsets1 <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D ((Ptr Offset3D pdstOffsets forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` Int 12 :: Ptr Offset3D)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 Storable ImageBlit where sizeOf :: ImageBlit -> Int sizeOf ~ImageBlit _ = Int 80 alignment :: ImageBlit -> Int alignment ~ImageBlit _ = Int 4 peek :: ("pRegions" ::: Ptr ImageBlit) -> IO ImageBlit peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pRegions" ::: Ptr ImageBlit) -> ImageBlit -> IO () poke "pRegions" ::: Ptr ImageBlit ptr ImageBlit poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr ImageBlit ptr ImageBlit poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ImageBlit where zero :: ImageBlit zero = ImageSubresourceLayers -> (Offset3D, Offset3D) -> ImageSubresourceLayers -> (Offset3D, Offset3D) -> ImageBlit ImageBlit forall a. Zero a => a zero (forall a. Zero a => a zero, forall a. Zero a => a zero) forall a. Zero a => a zero (forall a. Zero a => a zero, forall a. Zero a => a zero) -- | VkBufferImageCopy - Structure specifying a buffer image copy operation -- -- == Valid Usage -- -- - #VUID-VkBufferImageCopy-bufferRowLength-09101# @bufferRowLength@ -- /must/ be @0@, or greater than or equal to the @width@ member of -- @imageExtent@ -- -- - #VUID-VkBufferImageCopy-bufferImageHeight-09102# @bufferImageHeight@ -- /must/ be @0@, or greater than or equal to the @height@ member of -- @imageExtent@ -- -- - #VUID-VkBufferImageCopy-aspectMask-09103# The @aspectMask@ member of -- @imageSubresource@ /must/ only have a single bit set -- -- - #VUID-VkBufferImageCopy-imageExtent-06659# @imageExtent.width@ -- /must/ not be 0 -- -- - #VUID-VkBufferImageCopy-imageExtent-06660# @imageExtent.height@ -- /must/ not be 0 -- -- - #VUID-VkBufferImageCopy-imageExtent-06661# @imageExtent.depth@ -- /must/ not be 0 -- -- == Valid Usage (Implicit) -- -- - #VUID-VkBufferImageCopy-imageSubresource-parameter# -- @imageSubresource@ /must/ be a valid 'ImageSubresourceLayers' -- structure -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall b. BufferImageCopy -> (("pRegions" ::: Ptr BufferImageCopy) -> IO b) -> IO b withCStruct BufferImageCopy x ("pRegions" ::: Ptr BufferImageCopy) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 56 forall a b. (a -> b) -> a -> b $ \"pRegions" ::: Ptr BufferImageCopy p -> 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 :: forall b. ("pRegions" ::: Ptr BufferImageCopy) -> BufferImageCopy -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr BufferImageCopy p BufferImageCopy{"firstViewport" ::: Word32 "offset" ::: DeviceSize ImageSubresourceLayers Offset3D Extent3D imageExtent :: Extent3D imageOffset :: Offset3D imageSubresource :: ImageSubresourceLayers bufferImageHeight :: "firstViewport" ::: Word32 bufferRowLength :: "firstViewport" ::: Word32 bufferOffset :: "offset" ::: DeviceSize $sel:imageExtent:BufferImageCopy :: BufferImageCopy -> Extent3D $sel:imageOffset:BufferImageCopy :: BufferImageCopy -> Offset3D $sel:imageSubresource:BufferImageCopy :: BufferImageCopy -> ImageSubresourceLayers $sel:bufferImageHeight:BufferImageCopy :: BufferImageCopy -> "firstViewport" ::: Word32 $sel:bufferRowLength:BufferImageCopy :: BufferImageCopy -> "firstViewport" ::: Word32 $sel:bufferOffset:BufferImageCopy :: BufferImageCopy -> "offset" ::: DeviceSize ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr DeviceSize)) ("offset" ::: DeviceSize bufferOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) ("firstViewport" ::: Word32 bufferRowLength) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) ("firstViewport" ::: Word32 bufferImageHeight) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers imageSubresource) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Offset3D)) (Offset3D imageOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Extent3D)) (Extent3D imageExtent) IO b f cStructSize :: Int cStructSize = Int 56 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. ("pRegions" ::: Ptr BufferImageCopy) -> IO b -> IO b pokeZeroCStruct "pRegions" ::: Ptr BufferImageCopy p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr DeviceSize)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Offset3D)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Extent3D)) (forall a. Zero a => a zero) IO b f instance FromCStruct BufferImageCopy where peekCStruct :: ("pRegions" ::: Ptr BufferImageCopy) -> IO BufferImageCopy peekCStruct "pRegions" ::: Ptr BufferImageCopy p = do "offset" ::: DeviceSize bufferOffset <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr DeviceSize)) "firstViewport" ::: Word32 bufferRowLength <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) "firstViewport" ::: Word32 bufferImageHeight <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) ImageSubresourceLayers imageSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr ImageSubresourceLayers)) Offset3D imageOffset <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Offset3D)) Extent3D imageExtent <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Extent3D (("pRegions" ::: Ptr BufferImageCopy p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Extent3D)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("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 Storable BufferImageCopy where sizeOf :: BufferImageCopy -> Int sizeOf ~BufferImageCopy _ = Int 56 alignment :: BufferImageCopy -> Int alignment ~BufferImageCopy _ = Int 8 peek :: ("pRegions" ::: Ptr BufferImageCopy) -> IO BufferImageCopy peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pRegions" ::: Ptr BufferImageCopy) -> BufferImageCopy -> IO () poke "pRegions" ::: Ptr BufferImageCopy ptr BufferImageCopy poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr BufferImageCopy ptr BufferImageCopy poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero BufferImageCopy where zero :: BufferImageCopy zero = ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ImageSubresourceLayers -> Offset3D -> Extent3D -> BufferImageCopy BufferImageCopy forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkImageResolve - Structure specifying an image resolve operation -- -- == Valid Usage -- -- - #VUID-VkImageResolve-aspectMask-00266# The @aspectMask@ member of -- @srcSubresource@ and @dstSubresource@ /must/ only contain -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- -- - #VUID-VkImageResolve-layerCount-08803# If neither of the -- @layerCount@ members of @srcSubresource@ or @dstSubresource@ are -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the -- @layerCount@ member of @srcSubresource@ and @dstSubresource@ /must/ -- match -- -- - #VUID-VkImageResolve-maintenance5-08802# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance5 maintenance5> -- feature is not enabled, the @layerCount@ member of @srcSubresource@ -- or @dstSubresource@ /must/ not be -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' -- -- - #VUID-VkImageResolve-layerCount-08804# If one of the @layerCount@ -- members of @srcSubresource@ or @dstSubresource@ is -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the other -- member /must/ be either -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' or equal to the -- @arrayLayers@ member of the 'Vulkan.Core10.Image.ImageCreateInfo' -- used to create the image minus @baseArrayLayer@ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkImageResolve-srcSubresource-parameter# @srcSubresource@ -- /must/ be a valid 'ImageSubresourceLayers' structure -- -- - #VUID-VkImageResolve-dstSubresource-parameter# @dstSubresource@ -- /must/ be a valid 'ImageSubresourceLayers' structure -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 :: forall b. ImageResolve -> (("pRegions" ::: Ptr ImageResolve) -> IO b) -> IO b withCStruct ImageResolve x ("pRegions" ::: Ptr ImageResolve) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 68 forall a b. (a -> b) -> a -> b $ \"pRegions" ::: Ptr ImageResolve p -> 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 :: forall b. ("pRegions" ::: Ptr ImageResolve) -> ImageResolve -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr ImageResolve p ImageResolve{ImageSubresourceLayers Offset3D Extent3D extent :: Extent3D dstOffset :: Offset3D dstSubresource :: ImageSubresourceLayers srcOffset :: Offset3D srcSubresource :: ImageSubresourceLayers $sel:extent:ImageResolve :: ImageResolve -> Extent3D $sel:dstOffset:ImageResolve :: ImageResolve -> Offset3D $sel:dstSubresource:ImageResolve :: ImageResolve -> ImageSubresourceLayers $sel:srcOffset:ImageResolve :: ImageResolve -> Offset3D $sel:srcSubresource:ImageResolve :: ImageResolve -> ImageSubresourceLayers ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers srcSubresource) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Offset3D)) (Offset3D srcOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageSubresourceLayers)) (ImageSubresourceLayers dstSubresource) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Offset3D)) (Offset3D dstOffset) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Extent3D)) (Extent3D extent) IO b f cStructSize :: Int cStructSize = Int 68 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. ("pRegions" ::: Ptr ImageResolve) -> IO b -> IO b pokeZeroCStruct "pRegions" ::: Ptr ImageResolve p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Offset3D)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageSubresourceLayers)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Offset3D)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Extent3D)) (forall a. Zero a => a zero) IO b f instance FromCStruct ImageResolve where peekCStruct :: ("pRegions" ::: Ptr ImageResolve) -> IO ImageResolve peekCStruct "pRegions" ::: Ptr ImageResolve p = do ImageSubresourceLayers srcSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageSubresourceLayers)) Offset3D srcOffset <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Offset3D)) ImageSubresourceLayers dstSubresource <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceLayers (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageSubresourceLayers)) Offset3D dstOffset <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Offset3D (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 44 :: Ptr Offset3D)) Extent3D extent <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Extent3D (("pRegions" ::: Ptr ImageResolve p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Extent3D)) forall (f :: * -> *) a. Applicative f => a -> f a pure 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 Storable ImageResolve where sizeOf :: ImageResolve -> Int sizeOf ~ImageResolve _ = Int 68 alignment :: ImageResolve -> Int alignment ~ImageResolve _ = Int 4 peek :: ("pRegions" ::: Ptr ImageResolve) -> IO ImageResolve peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pRegions" ::: Ptr ImageResolve) -> ImageResolve -> IO () poke "pRegions" ::: Ptr ImageResolve ptr ImageResolve poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pRegions" ::: Ptr ImageResolve ptr ImageResolve poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ImageResolve where zero :: ImageResolve zero = ImageSubresourceLayers -> Offset3D -> ImageSubresourceLayers -> Offset3D -> Extent3D -> ImageResolve ImageResolve forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkRenderPassBeginInfo - Structure specifying render pass begin -- information -- -- = 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://registry.khronos.org/vulkan/specs/1.3-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. -- -- If multiview is enabled in @renderPass@, and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiview-per-view-render-areas multiviewPerViewRenderAreas> -- feature is enabled, and there is an instance of -- 'Vulkan.Extensions.VK_QCOM_multiview_per_view_render_areas.MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM' -- included in the @pNext@ chain with @perViewRenderAreaCount@ not equal to -- @0@, then the elements of -- 'Vulkan.Extensions.VK_QCOM_multiview_per_view_render_areas.MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM'::@pPerViewRenderAreas@ -- override @renderArea@ and define a render area for each view. In this -- case, @renderArea@ /must/ be set to an area at least as large as the -- union of all the per-view render areas. -- -- If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-subpassShading subpassShading> -- feature is enabled, then @renderArea@ /must/ equal the framebuffer -- dimensions. -- -- 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 -- -- - #VUID-VkRenderPassBeginInfo-clearValueCount-00902# @clearValueCount@ -- /must/ be greater than the largest attachment index in @renderPass@ -- specifying a @loadOp@ (or @stencilLoadOp@, if the attachment has a -- depth\/stencil format) of -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' -- -- - #VUID-VkRenderPassBeginInfo-clearValueCount-04962# If -- @clearValueCount@ is not @0@, @pClearValues@ /must/ be a valid -- pointer to an array of @clearValueCount@ 'ClearValue' unions -- -- - #VUID-VkRenderPassBeginInfo-renderPass-00904# @renderPass@ /must/ be -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-compatibility compatible> -- with the @renderPass@ member of the -- 'Vulkan.Core10.Pass.FramebufferCreateInfo' structure specified when -- creating @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-None-08996# If -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo'::@deviceRenderAreaCount@ -- is 0, @renderArea.extent.width@ /must/ be greater than 0 -- -- - #VUID-VkRenderPassBeginInfo-None-08997# If -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo'::@deviceRenderAreaCount@ -- is 0, @renderArea.extent.height@ /must/ be greater than 0 -- -- - #VUID-VkRenderPassBeginInfo-pNext-02850# 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 -- -- - #VUID-VkRenderPassBeginInfo-pNext-02851# 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 -- -- - #VUID-VkRenderPassBeginInfo-pNext-02852# 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.extent.width@ /must/ be less -- than or equal to 'Vulkan.Core10.Pass.FramebufferCreateInfo'::@width@ -- the @framebuffer@ was created with -- -- - #VUID-VkRenderPassBeginInfo-pNext-02853# 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.extent.height@ /must/ be less -- than or equal to -- 'Vulkan.Core10.Pass.FramebufferCreateInfo'::@height@ the -- @framebuffer@ was created with -- -- - #VUID-VkRenderPassBeginInfo-pNext-02856# If the @pNext@ chain -- contains -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo', -- @offset.x@ + @extent.width@ of each element of @pDeviceRenderAreas@ -- /must/ be less than or equal to -- 'Vulkan.Core10.Pass.FramebufferCreateInfo'::@width@ the -- @framebuffer@ was created with -- -- - #VUID-VkRenderPassBeginInfo-pNext-02857# If the @pNext@ chain -- contains -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupRenderPassBeginInfo', -- @offset.y@ + @extent.height@ of each element of @pDeviceRenderAreas@ -- /must/ be less than or equal to -- 'Vulkan.Core10.Pass.FramebufferCreateInfo'::@height@ the -- @framebuffer@ was created with -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03207# 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 -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03208# 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@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-02780# 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@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03209# 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'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-04627# 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 -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-inherited-usage an inherited usage> -- equal to the @usage@ member of the corresponding element of -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03211# 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'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03212# 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'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03213# 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'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03214# 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'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03215# 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'::@pAttachmentImageInfos@ -- used to create @framebuffer@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-03216# 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@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-09353# If @framebuffer@ was -- created with a 'Vulkan.Core10.Pass.FramebufferCreateInfo'::@flags@ -- value that included -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- and the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-nullColorAttachmentWithExternalFormatResolve nullColorAttachmentWithExternalFormatResolve> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', the format of the color -- attachment for each subpass that includes an external format image -- as a resolve attachment /must/ have a format equal to the value of -- 'Vulkan.Extensions.VK_ANDROID_external_format_resolve.AndroidHardwareBufferFormatResolvePropertiesANDROID'::@colorAttachmentFormat@ -- as returned by a call to -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getAndroidHardwareBufferPropertiesANDROID' -- for the Android hardware buffer that was used to create the image -- view use as its resolve attachment -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-09354# 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.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- equal to -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- in the @pNext@ chain of the corresponding -- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentDescription2' -- structure used to create @renderPass@ -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-09047# 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@ , or -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' if -- @renderPass@ was created with -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT' -- structure in the @pNext@ chain with -- @multisampledRenderToSingleSampledEnable@ equal to -- 'Vulkan.Core10.FundamentalTypes.TRUE' -- -- - #VUID-VkRenderPassBeginInfo-pNext-02869# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_render_pass_transform.RenderPassTransformBeginInfoQCOM', -- @renderArea.offset@ /must/ equal (0,0) -- -- - #VUID-VkRenderPassBeginInfo-pNext-02870# 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 -- -- - #VUID-VkRenderPassBeginInfo-perViewRenderAreaCount-07859# If the -- @perViewRenderAreaCount@ member of a -- 'Vulkan.Extensions.VK_QCOM_multiview_per_view_render_areas.MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM' -- structure included in the @pNext@ chain is not @0@, then the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiview-per-view-render-areas multiviewPerViewRenderAreas> -- feature /must/ be enabled. -- -- - #VUID-VkRenderPassBeginInfo-perViewRenderAreaCount-07860# If the -- @perViewRenderAreaCount@ member of a -- 'Vulkan.Extensions.VK_QCOM_multiview_per_view_render_areas.MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM' -- structure included in the @pNext@ chain is not @0@, then -- @renderArea@ /must/ specify a render area that includes the union of -- all per view render areas. -- -- == Valid Usage (Implicit) -- -- - #VUID-VkRenderPassBeginInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO' -- -- - #VUID-VkRenderPassBeginInfo-pNext-pNext# 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.Extensions.VK_QCOM_multiview_per_view_render_areas.MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM', -- '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' -- -- - #VUID-VkRenderPassBeginInfo-sType-unique# The @sType@ value of each -- struct in the @pNext@ chain /must/ be unique -- -- - #VUID-VkRenderPassBeginInfo-renderPass-parameter# @renderPass@ -- /must/ be a valid 'Vulkan.Core10.Handles.RenderPass' handle -- -- - #VUID-VkRenderPassBeginInfo-framebuffer-parameter# @framebuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.Framebuffer' handle -- -- - #VUID-VkRenderPassBeginInfo-commonparent# Both of @framebuffer@, and -- @renderPass@ /must/ have been created, allocated, or retrieved from -- the same 'Vulkan.Core10.Handles.Device' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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. forall (es :: [*]). RenderPassBeginInfo es -> Chain es next :: Chain es , -- | @renderPass@ is the render pass to begin an instance of. forall (es :: [*]). RenderPassBeginInfo es -> RenderPass renderPass :: RenderPass , -- | @framebuffer@ is the framebuffer containing the attachments that are -- used with the render pass. forall (es :: [*]). 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. forall (es :: [*]). RenderPassBeginInfo es -> Rect2D renderArea :: Rect2D , -- | @pClearValues@ is a pointer to an array of @clearValueCount@ -- 'ClearValue' structures containing 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. forall (es :: [*]). 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 extensibleTypeName :: String extensibleTypeName = String "RenderPassBeginInfo" setNext :: forall (ds :: [*]) (es :: [*]). RenderPassBeginInfo ds -> Chain es -> RenderPassBeginInfo es setNext RenderPassBeginInfo{Vector ClearValue Chain ds Rect2D RenderPass Framebuffer clearValues :: Vector ClearValue renderArea :: Rect2D framebuffer :: Framebuffer renderPass :: RenderPass next :: Chain ds $sel:clearValues:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Vector ClearValue $sel:renderArea:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Rect2D $sel:framebuffer:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Framebuffer $sel:renderPass:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> RenderPass $sel:next:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Chain es ..} Chain es next' = RenderPassBeginInfo{$sel:next:RenderPassBeginInfo :: Chain es next = Chain es next', Vector ClearValue Rect2D RenderPass Framebuffer clearValues :: Vector ClearValue renderArea :: Rect2D framebuffer :: Framebuffer renderPass :: RenderPass $sel:clearValues:RenderPassBeginInfo :: Vector ClearValue $sel:renderArea:RenderPassBeginInfo :: Rect2D $sel:framebuffer:RenderPassBeginInfo :: Framebuffer $sel:renderPass:RenderPassBeginInfo :: RenderPass ..} getNext :: forall (es :: [*]). RenderPassBeginInfo es -> Chain es getNext RenderPassBeginInfo{Vector ClearValue Chain es Rect2D RenderPass Framebuffer clearValues :: Vector ClearValue renderArea :: Rect2D framebuffer :: Framebuffer renderPass :: RenderPass next :: Chain es $sel:clearValues:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Vector ClearValue $sel:renderArea:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Rect2D $sel:framebuffer:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Framebuffer $sel:renderPass:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> RenderPass $sel:next:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Chain es ..} = Chain es next extends :: forall e b proxy. Typeable e => proxy e -> (Extends RenderPassBeginInfo e => b) -> Maybe b extends :: forall e b (proxy :: * -> *). Typeable e => proxy e -> (Extends RenderPassBeginInfo e => b) -> Maybe b extends proxy e _ Extends RenderPassBeginInfo e => b f | Just e :~: MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @MultiviewPerViewRenderAreasRenderPassBeginInfoQCOM = forall a. a -> Maybe a Just Extends RenderPassBeginInfo e => b f | Just e :~: RenderPassTransformBeginInfoQCOM Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @RenderPassTransformBeginInfoQCOM = forall a. a -> Maybe a Just Extends RenderPassBeginInfo e => b f | Just e :~: RenderPassAttachmentBeginInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @RenderPassAttachmentBeginInfo = forall a. a -> Maybe a Just Extends RenderPassBeginInfo e => b f | Just e :~: RenderPassSampleLocationsBeginInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @RenderPassSampleLocationsBeginInfoEXT = forall a. a -> Maybe a Just Extends RenderPassBeginInfo e => b f | Just e :~: DeviceGroupRenderPassBeginInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @DeviceGroupRenderPassBeginInfo = forall a. a -> Maybe a Just Extends RenderPassBeginInfo e => b f | Bool otherwise = forall a. Maybe a Nothing instance ( Extendss RenderPassBeginInfo es , PokeChain es ) => ToCStruct (RenderPassBeginInfo es) where withCStruct :: forall b. RenderPassBeginInfo es -> (Ptr (RenderPassBeginInfo es) -> IO b) -> IO b withCStruct RenderPassBeginInfo es x Ptr (RenderPassBeginInfo es) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 64 forall a b. (a -> b) -> a -> b $ \Ptr (RenderPassBeginInfo es) p -> 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 :: forall b. Ptr (RenderPassBeginInfo es) -> RenderPassBeginInfo es -> IO b -> IO b pokeCStruct Ptr (RenderPassBeginInfo es) p RenderPassBeginInfo{Vector ClearValue Chain es Rect2D RenderPass Framebuffer clearValues :: Vector ClearValue renderArea :: Rect2D framebuffer :: Framebuffer renderPass :: RenderPass next :: Chain es $sel:clearValues:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Vector ClearValue $sel:renderArea:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Rect2D $sel:framebuffer:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Framebuffer $sel:renderPass:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> RenderPass $sel:next:RenderPassBeginInfo :: forall (es :: [*]). RenderPassBeginInfo es -> Chain es ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO) "data" ::: Ptr () pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (es :: [*]) a. PokeChain es => Chain es -> (Ptr (Chain es) -> IO a) -> IO a withChain (Chain es next) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) "data" ::: Ptr () pNext'' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr RenderPass)) (RenderPass renderPass) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Framebuffer)) (Framebuffer framebuffer) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Rect2D)) (Rect2D renderArea) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector ClearValue clearValues)) :: Word32)) Ptr ClearValue pPClearValues' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ClearValue ((forall a. Vector a -> Int Data.Vector.length (Vector ClearValue clearValues)) forall a. Num a => a -> a -> a * Int 16) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ClearValue e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct (Ptr ClearValue pPClearValues' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 16 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ClearValue) (ClearValue e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) (Vector ClearValue clearValues) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (Ptr ClearValue))) (Ptr ClearValue pPClearValues') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 64 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr (RenderPassBeginInfo es) -> IO b -> IO b pokeZeroCStruct Ptr (RenderPassBeginInfo es) p IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO) "data" ::: Ptr () pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (es :: [*]) a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a withZeroChain @es forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) "data" ::: Ptr () pNext' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr RenderPass)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Framebuffer)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassBeginInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Rect2D)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f instance es ~ '[] => Zero (RenderPassBeginInfo es) where zero :: RenderPassBeginInfo es zero = forall (es :: [*]). Chain es -> RenderPass -> Framebuffer -> Rect2D -> Vector ClearValue -> RenderPassBeginInfo es RenderPassBeginInfo () forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Monoid a => a mempty -- | VkClearDepthStencilValue - Structure specifying a clear depth stencil -- value -- -- == Valid Usage -- -- - #VUID-VkClearDepthStencilValue-depth-00022# Unless the -- @VK_EXT_depth_range_unrestricted@ extension is enabled @depth@ -- /must/ be between @0.0@ and @1.0@, inclusive -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 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 :: forall b. ClearDepthStencilValue -> (("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b) -> IO b withCStruct ClearDepthStencilValue x ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 8 forall a b. (a -> b) -> a -> b $ \"pDepthStencil" ::: Ptr ClearDepthStencilValue p -> 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 :: forall b. ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> ClearDepthStencilValue -> IO b -> IO b pokeCStruct "pDepthStencil" ::: Ptr ClearDepthStencilValue p ClearDepthStencilValue{"lineWidth" ::: Float "firstViewport" ::: Word32 stencil :: "firstViewport" ::: Word32 depth :: "lineWidth" ::: Float $sel:stencil:ClearDepthStencilValue :: ClearDepthStencilValue -> "firstViewport" ::: Word32 $sel:depth:ClearDepthStencilValue :: ClearDepthStencilValue -> "lineWidth" ::: Float ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr CFloat)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float depth)) forall a. Storable a => Ptr a -> a -> IO () poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) ("firstViewport" ::: Word32 stencil) IO b f cStructSize :: Int cStructSize = Int 8 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO b -> IO b pokeZeroCStruct "pDepthStencil" ::: Ptr ClearDepthStencilValue p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr CFloat)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat (forall a. Zero a => a zero)) forall a. Storable a => Ptr a -> a -> IO () poke (("pDepthStencil" ::: Ptr ClearDepthStencilValue p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct ClearDepthStencilValue where peekCStruct :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO ClearDepthStencilValue peekCStruct "pDepthStencil" ::: Ptr ClearDepthStencilValue p = do "lineWidth" ::: CFloat depth <- forall a. Storable a => Ptr a -> IO a peek @CFloat (("pDepthStencil" ::: Ptr ClearDepthStencilValue p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr CFloat)) "firstViewport" ::: Word32 stencil <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pDepthStencil" ::: Ptr ClearDepthStencilValue p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("lineWidth" ::: Float) -> ("firstViewport" ::: Word32) -> ClearDepthStencilValue ClearDepthStencilValue (coerce :: forall a b. Coercible a b => a -> b coerce @CFloat @Float "lineWidth" ::: CFloat depth) "firstViewport" ::: Word32 stencil instance Storable ClearDepthStencilValue where sizeOf :: ClearDepthStencilValue -> Int sizeOf ~ClearDepthStencilValue _ = Int 8 alignment :: ClearDepthStencilValue -> Int alignment ~ClearDepthStencilValue _ = Int 4 peek :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> IO ClearDepthStencilValue peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pDepthStencil" ::: Ptr ClearDepthStencilValue) -> ClearDepthStencilValue -> IO () poke "pDepthStencil" ::: Ptr ClearDepthStencilValue ptr ClearDepthStencilValue poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pDepthStencil" ::: Ptr ClearDepthStencilValue ptr ClearDepthStencilValue poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ClearDepthStencilValue where zero :: ClearDepthStencilValue zero = ("lineWidth" ::: Float) -> ("firstViewport" ::: Word32) -> ClearDepthStencilValue ClearDepthStencilValue forall a. Zero a => a zero forall a. Zero a => a zero -- | VkClearAttachment - Structure specifying a clear attachment -- -- == Valid Usage -- -- - #VUID-VkClearAttachment-aspectMask-00019# 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' -- -- - #VUID-VkClearAttachment-aspectMask-00020# @aspectMask@ /must/ not -- include -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT' -- -- - #VUID-VkClearAttachment-aspectMask-02246# @aspectMask@ /must/ not -- include @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index /i/ -- -- - #VUID-VkClearAttachment-clearValue-00021# @clearValue@ /must/ be a -- valid 'ClearValue' union -- -- == Valid Usage (Implicit) -- -- - #VUID-VkClearAttachment-aspectMask-parameter# @aspectMask@ /must/ be -- a valid combination of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values -- -- - #VUID-VkClearAttachment-aspectMask-requiredbitmask# @aspectMask@ -- /must/ not be @0@ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- '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 into the currently bound -- color attachments. ClearAttachment -> "firstViewport" ::: Word32 colorAttachment :: Word32 , -- | @clearValue@ is the color or depth\/stencil value to clear the -- attachment to, as described in -- <https://registry.khronos.org/vulkan/specs/1.3-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 :: forall b. ClearAttachment -> (("pAttachments" ::: Ptr ClearAttachment) -> IO b) -> IO b withCStruct ClearAttachment x ("pAttachments" ::: Ptr ClearAttachment) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 24 forall a b. (a -> b) -> a -> b $ \"pAttachments" ::: Ptr ClearAttachment p -> 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 :: forall b. ("pAttachments" ::: Ptr ClearAttachment) -> ClearAttachment -> IO b -> IO b pokeCStruct "pAttachments" ::: Ptr ClearAttachment p ClearAttachment{"firstViewport" ::: Word32 ImageAspectFlags ClearValue clearValue :: ClearValue colorAttachment :: "firstViewport" ::: Word32 aspectMask :: ImageAspectFlags $sel:clearValue:ClearAttachment :: ClearAttachment -> ClearValue $sel:colorAttachment:ClearAttachment :: ClearAttachment -> "firstViewport" ::: Word32 $sel:aspectMask:ClearAttachment :: ClearAttachment -> ImageAspectFlags ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pAttachments" ::: Ptr ClearAttachment p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags aspectMask) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pAttachments" ::: Ptr ClearAttachment p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) ("firstViewport" ::: Word32 colorAttachment) forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct (("pAttachments" ::: Ptr ClearAttachment p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr ClearValue)) (ClearValue clearValue) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ()) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 24 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. ("pAttachments" ::: Ptr ClearAttachment) -> IO b -> IO b pokeZeroCStruct "pAttachments" ::: Ptr ClearAttachment p IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pAttachments" ::: Ptr ClearAttachment p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pAttachments" ::: Ptr ClearAttachment p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (forall a. Zero a => a zero) forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct (("pAttachments" ::: Ptr ClearAttachment p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr ClearValue)) (forall a. Zero a => a zero) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ()) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f instance Zero ClearAttachment where zero :: ClearAttachment zero = ImageAspectFlags -> ("firstViewport" ::: Word32) -> ClearValue -> ClearAttachment ClearAttachment forall a. Zero a => a zero forall a. Zero a => a zero 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 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 :: forall b. ClearColorValue -> (("pColor" ::: Ptr ClearColorValue) -> IO b) -> IO b withCStruct ClearColorValue x ("pColor" ::: Ptr ClearColorValue) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 16 forall a b. (a -> b) -> a -> b $ \"pColor" ::: Ptr ClearColorValue p -> 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 :: forall b. ("pColor" ::: Ptr ClearColorValue) -> ClearColorValue -> IO b -> IO b pokeCStruct "pColor" ::: Ptr ClearColorValue p = (forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. a -> b -> a const) forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r runContT forall b c a. (b -> c) -> (a -> b) -> a -> c . \case Float32 "lineWidth" ::: Float v0 "lineWidth" ::: Float v1 "lineWidth" ::: Float v2 "lineWidth" ::: Float v3 -> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ do let pFloat32 :: Ptr ("lineWidth" ::: CFloat) pFloat32 = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (forall a b. Ptr a -> Ptr b castPtr @_ @(FixedArray 4 CFloat) "pColor" ::: Ptr ClearColorValue p) case (("lineWidth" ::: Float v0, "lineWidth" ::: Float v1, "lineWidth" ::: Float v2, "lineWidth" ::: Float v3)) of ("lineWidth" ::: Float e0, "lineWidth" ::: Float e1, "lineWidth" ::: Float e2, "lineWidth" ::: Float e3) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pFloat32 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e0)) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pFloat32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e1)) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pFloat32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e2)) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pFloat32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e3)) Int32 "vertexOffset" ::: Int32 v0 "vertexOffset" ::: Int32 v1 "vertexOffset" ::: Int32 v2 "vertexOffset" ::: Int32 v3 -> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ do let pInt32 :: Ptr ("vertexOffset" ::: Int32) pInt32 = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (forall a b. Ptr a -> Ptr b castPtr @_ @(FixedArray 4 Int32) "pColor" ::: Ptr ClearColorValue p) case (("vertexOffset" ::: Int32 v0, "vertexOffset" ::: Int32 v1, "vertexOffset" ::: Int32 v2, "vertexOffset" ::: Int32 v3)) of ("vertexOffset" ::: Int32 e0, "vertexOffset" ::: Int32 e1, "vertexOffset" ::: Int32 e2, "vertexOffset" ::: Int32 e3) -> do forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("vertexOffset" ::: Int32) pInt32 :: Ptr Int32) ("vertexOffset" ::: Int32 e0) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("vertexOffset" ::: Int32) pInt32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Int32) ("vertexOffset" ::: Int32 e1) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("vertexOffset" ::: Int32) pInt32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Int32) ("vertexOffset" ::: Int32 e2) forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("vertexOffset" ::: Int32) pInt32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Int32) ("vertexOffset" ::: Int32 e3) Uint32 "firstViewport" ::: Word32 v0 "firstViewport" ::: Word32 v1 "firstViewport" ::: Word32 v2 "firstViewport" ::: Word32 v3 -> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ do let pUint32 :: "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pUint32 = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr (forall a b. Ptr a -> Ptr b castPtr @_ @(FixedArray 4 Word32) "pColor" ::: Ptr ClearColorValue p) case (("firstViewport" ::: Word32 v0, "firstViewport" ::: Word32 v1, "firstViewport" ::: Word32 v2, "firstViewport" ::: Word32 v3)) of ("firstViewport" ::: Word32 e0, "firstViewport" ::: Word32 e1, "firstViewport" ::: Word32 e2, "firstViewport" ::: Word32 e3) -> do forall a. Storable a => Ptr a -> a -> IO () poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pUint32 :: Ptr Word32) ("firstViewport" ::: Word32 e0) forall a. Storable a => Ptr a -> a -> IO () poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pUint32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32) ("firstViewport" ::: Word32 e1) forall a. Storable a => Ptr a -> a -> IO () poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pUint32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32) ("firstViewport" ::: Word32 e2) forall a. Storable a => Ptr a -> a -> IO () poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pUint32 forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32) ("firstViewport" ::: Word32 e3) pokeZeroCStruct :: Ptr ClearColorValue -> IO b -> IO b pokeZeroCStruct :: forall b. ("pColor" ::: Ptr ClearColorValue) -> IO b -> IO b pokeZeroCStruct "pColor" ::: Ptr ClearColorValue _ IO b f = IO b f cStructSize :: Int cStructSize = Int 16 cStructAlignment :: Int cStructAlignment = Int 4 instance Zero ClearColorValue where zero :: ClearColorValue zero = ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> ClearColorValue Float32 forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero data ClearValue = Color ClearColorValue | DepthStencil ClearDepthStencilValue deriving (Int -> ClearValue -> ShowS [ClearValue] -> ShowS ClearValue -> String 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 :: forall b. ClearValue -> (Ptr ClearValue -> IO b) -> IO b withCStruct ClearValue x Ptr ClearValue -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 16 forall a b. (a -> b) -> a -> b $ \Ptr ClearValue p -> 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 :: forall b. Ptr ClearValue -> ClearValue -> IO b -> IO b pokeCStruct Ptr ClearValue p = (forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. a -> b -> a const) forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r runContT forall b c a. (b -> c) -> (a -> b) -> a -> c . \case Color ClearColorValue v -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct (forall a b. Ptr a -> Ptr b castPtr @_ @ClearColorValue Ptr ClearValue p) (ClearColorValue v) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ()) DepthStencil ClearDepthStencilValue v -> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (forall a b. Ptr a -> Ptr b castPtr @_ @ClearDepthStencilValue Ptr ClearValue p) (ClearDepthStencilValue v) pokeZeroCStruct :: Ptr ClearValue -> IO b -> IO b pokeZeroCStruct :: forall b. Ptr ClearValue -> IO b -> IO b pokeZeroCStruct Ptr ClearValue _ IO b f = IO b f cStructSize :: Int cStructSize = Int 16 cStructAlignment :: Int cStructAlignment = Int 4 instance Zero ClearValue where zero :: ClearValue zero = ClearColorValue -> ClearValue Color forall a. Zero a => a zero